{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TupleSections #-}
module Modelling.CdOd.RepairCd (
InValidOption (..),
RelationshipChangeWithArticle,
RepairCdConfig (..),
RepairCdInstance (..),
RepairCdTaskTextElement (..),
WeakeningKind (..),
checkClassConfigAndChanges,
checkRepairCdConfig,
checkRepairCdInstance,
classAndNonInheritanceNames,
defaultRepairCdConfig,
defaultRepairCdInstance,
generateSetOfCds,
mapInValidOption,
mapInValidOptionM,
renameInstance,
repairCd,
repairCdEvaluation,
repairCdSolution,
repairCdSyntax,
repairCdTask,
StructuralWeakening (..),
(.&.),
illegalStructuralWeakenings,
legalStructuralWeakenings,
toProperty,
) where
import qualified Modelling.CdOd.CdAndChanges.Transform as Changes (
transformChanges,
transformImproveCd,
)
import qualified Data.Bimap as BM (fromList)
import qualified Data.Map as M (
elems,
filter,
fromAscList,
fromList,
keys,
toList,
traverseWithKey,
)
import Capabilities.Alloy (MonadAlloy, getInstances)
import Capabilities.Cache (MonadCache)
import Capabilities.Diagrams (MonadDiagrams)
import Capabilities.Graphviz (MonadGraphviz)
import Modelling.Auxiliary.Common (
Randomise (randomise),
RandomiseLayout (randomiseLayout),
RandomiseNames (randomiseNames),
TaskGenerationException (NoInstanceAvailable),
)
import Modelling.Auxiliary.Output (
addPretext,
checkTaskText,
hoveringInformation,
simplifiedInformation,
uniform, extra,
)
import Modelling.Auxiliary.Shuffle.All (shuffleEverything)
import Modelling.CdOd.Auxiliary.Util (alloyInstanceToOd)
import Modelling.CdOd.CD2Alloy.Transform (
ExtendsAnd (FieldPlacement),
LinguisticReuse (ExtendsAnd),
combineParts,
createRunCommand,
transform,
)
import Modelling.CdOd.CdAndChanges.Instance (
AnnotatedChangeAndCd (..),
ChangeAndCd (..),
GenericClassDiagramInstance (..),
fromInstance,
fromInstanceWithPredefinedNames,
nameClassDiagramInstance,
uniformlyAnnotateChangeAndCd,
)
import Modelling.CdOd.Output (
cacheCd,
)
import Modelling.CdOd.Phrasing (
phraseChange,
)
import Modelling.CdOd.Types (
AllowedProperties (..),
Annotation (..),
AnyCd,
AnyClassDiagram (..),
AnyRelationship,
ArticlePreference (..),
Cd,
CdConstraints (..),
CdDrawSettings (..),
CdMutation (AddRelationship, RemoveRelationship),
ClassConfig (..),
ClassDiagram (..),
LimitedLinking (..),
ObjectProperties (..),
Od,
OmittedDefaultMultiplicities (..),
Relationship (..),
RelationshipProperties (..),
allowNothing,
anonymiseObjects,
anyAssociationNames,
anyRelationshipName,
checkCdConstraints,
checkCdDrawProperties,
checkCdDrawSettings,
checkCdMutations,
checkClassConfig,
checkClassConfigAndObjectProperties,
checkClassConfigWithProperties,
checkObjectProperties,
classNames,
defaultCdConstraints,
defaultCdDrawSettings,
defaultProperties,
fromClassDiagram,
maxObjects,
relationshipName,
renameClassesAndRelationships,
shuffleAnyClassAndConnectionOrder,
shuffleClassAndConnectionOrder,
toArticleToUse,
toValidCd,
)
import Modelling.Types (Change (..))
import Control.Applicative (Alternative ((<|>)))
import Control.Monad ((>=>), forM, void, when, zipWithM)
import Control.Monad.Catch (MonadCatch, MonadThrow (throwM))
import Control.OutputCapable.Blocks (
ArticleToUse (DefiniteArticle),
GenericOutputCapable (..),
LangM,
Language (English, German),
OutputCapable,
Rated,
($=<<),
english,
enumerateM,
german,
multipleChoice,
multipleChoiceSyntax,
reRefuse,
translate,
translations,
)
import Control.OutputCapable.Blocks.Generic.Type (
GenericOutput (Code, Paragraph, Special, Translated),
)
import Control.OutputCapable.Blocks.Type (
SpecialOutput,
specialToOutputCapable,
)
import Control.Monad.Random (
MonadRandom,
RandT,
RandomGen,
evalRandT,
mkStdGen,
)
import Control.Monad.Trans (MonadTrans (lift))
import Data.Bifunctor (bimap, first, second)
import Data.Bitraversable (bimapM)
import Data.Containers.ListUtils (nubOrd, nubOrdOn)
import Data.Either (isRight)
import Data.Function (on)
import Data.List (deleteBy, singleton)
import Data.List.Extra (sortOn)
import Data.Map (Map)
import Data.Maybe (catMaybes, listToMaybe, mapMaybe)
import Data.Ratio ((%))
import Data.String.Interpolate (i, iii)
import GHC.Generics (Generic)
import System.Random.Shuffle (shuffle', shuffleM)
data StructuralWeakening = StructuralWeakening {
StructuralWeakening -> [Weakening]
weakeningName :: ![Weakening],
StructuralWeakening
-> RelationshipProperties -> RelationshipProperties
operation :: RelationshipProperties -> RelationshipProperties,
StructuralWeakening -> Bool -> Bool
validityChange :: Bool -> Bool
}
toProperty :: StructuralWeakening -> RelationshipProperties
toProperty :: StructuralWeakening -> RelationshipProperties
toProperty StructuralWeakening
p = StructuralWeakening
-> RelationshipProperties -> RelationshipProperties
operation StructuralWeakening
p RelationshipProperties
defaultProperties
isValidWeakening :: StructuralWeakening -> Bool
isValidWeakening :: StructuralWeakening -> Bool
isValidWeakening StructuralWeakening
p = StructuralWeakening -> Bool -> Bool
validityChange StructuralWeakening
p Bool
True
type RelationshipChangeWithArticle
= Annotation ArticleToUse (Change (AnyRelationship String String))
type CdChangeAndCd = InValidOption
(AnnotatedChangeAndCd ArticleToUse String String)
RelationshipChangeWithArticle
Od
type RelationshipChange = InValidOption
RelationshipChangeWithArticle
AnyCd
Cd
data InValidOption option forInvalidity forValidity = InValidOption {
forall option forInvalidity forValidity.
InValidOption option forInvalidity forValidity
-> Either forInvalidity forValidity
hint :: Either forInvalidity forValidity,
forall option forInvalidity forValidity.
InValidOption option forInvalidity forValidity -> option
option :: option
} deriving (InValidOption option forInvalidity forValidity
-> InValidOption option forInvalidity forValidity -> Bool
(InValidOption option forInvalidity forValidity
-> InValidOption option forInvalidity forValidity -> Bool)
-> (InValidOption option forInvalidity forValidity
-> InValidOption option forInvalidity forValidity -> Bool)
-> Eq (InValidOption option forInvalidity forValidity)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall option forInvalidity forValidity.
(Eq forInvalidity, Eq forValidity, Eq option) =>
InValidOption option forInvalidity forValidity
-> InValidOption option forInvalidity forValidity -> Bool
$c== :: forall option forInvalidity forValidity.
(Eq forInvalidity, Eq forValidity, Eq option) =>
InValidOption option forInvalidity forValidity
-> InValidOption option forInvalidity forValidity -> Bool
== :: InValidOption option forInvalidity forValidity
-> InValidOption option forInvalidity forValidity -> Bool
$c/= :: forall option forInvalidity forValidity.
(Eq forInvalidity, Eq forValidity, Eq option) =>
InValidOption option forInvalidity forValidity
-> InValidOption option forInvalidity forValidity -> Bool
/= :: InValidOption option forInvalidity forValidity
-> InValidOption option forInvalidity forValidity -> Bool
Eq, (forall x.
InValidOption option forInvalidity forValidity
-> Rep (InValidOption option forInvalidity forValidity) x)
-> (forall x.
Rep (InValidOption option forInvalidity forValidity) x
-> InValidOption option forInvalidity forValidity)
-> Generic (InValidOption option forInvalidity forValidity)
forall x.
Rep (InValidOption option forInvalidity forValidity) x
-> InValidOption option forInvalidity forValidity
forall x.
InValidOption option forInvalidity forValidity
-> Rep (InValidOption option forInvalidity forValidity) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall option forInvalidity forValidity x.
Rep (InValidOption option forInvalidity forValidity) x
-> InValidOption option forInvalidity forValidity
forall option forInvalidity forValidity x.
InValidOption option forInvalidity forValidity
-> Rep (InValidOption option forInvalidity forValidity) x
$cfrom :: forall option forInvalidity forValidity x.
InValidOption option forInvalidity forValidity
-> Rep (InValidOption option forInvalidity forValidity) x
from :: forall x.
InValidOption option forInvalidity forValidity
-> Rep (InValidOption option forInvalidity forValidity) x
$cto :: forall option forInvalidity forValidity x.
Rep (InValidOption option forInvalidity forValidity) x
-> InValidOption option forInvalidity forValidity
to :: forall x.
Rep (InValidOption option forInvalidity forValidity) x
-> InValidOption option forInvalidity forValidity
Generic, ReadPrec [InValidOption option forInvalidity forValidity]
ReadPrec (InValidOption option forInvalidity forValidity)
Int -> ReadS (InValidOption option forInvalidity forValidity)
ReadS [InValidOption option forInvalidity forValidity]
(Int -> ReadS (InValidOption option forInvalidity forValidity))
-> ReadS [InValidOption option forInvalidity forValidity]
-> ReadPrec (InValidOption option forInvalidity forValidity)
-> ReadPrec [InValidOption option forInvalidity forValidity]
-> Read (InValidOption option forInvalidity forValidity)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall option forInvalidity forValidity.
(Read forInvalidity, Read forValidity, Read option) =>
ReadPrec [InValidOption option forInvalidity forValidity]
forall option forInvalidity forValidity.
(Read forInvalidity, Read forValidity, Read option) =>
ReadPrec (InValidOption option forInvalidity forValidity)
forall option forInvalidity forValidity.
(Read forInvalidity, Read forValidity, Read option) =>
Int -> ReadS (InValidOption option forInvalidity forValidity)
forall option forInvalidity forValidity.
(Read forInvalidity, Read forValidity, Read option) =>
ReadS [InValidOption option forInvalidity forValidity]
$creadsPrec :: forall option forInvalidity forValidity.
(Read forInvalidity, Read forValidity, Read option) =>
Int -> ReadS (InValidOption option forInvalidity forValidity)
readsPrec :: Int -> ReadS (InValidOption option forInvalidity forValidity)
$creadList :: forall option forInvalidity forValidity.
(Read forInvalidity, Read forValidity, Read option) =>
ReadS [InValidOption option forInvalidity forValidity]
readList :: ReadS [InValidOption option forInvalidity forValidity]
$creadPrec :: forall option forInvalidity forValidity.
(Read forInvalidity, Read forValidity, Read option) =>
ReadPrec (InValidOption option forInvalidity forValidity)
readPrec :: ReadPrec (InValidOption option forInvalidity forValidity)
$creadListPrec :: forall option forInvalidity forValidity.
(Read forInvalidity, Read forValidity, Read option) =>
ReadPrec [InValidOption option forInvalidity forValidity]
readListPrec :: ReadPrec [InValidOption option forInvalidity forValidity]
Read, Int -> InValidOption option forInvalidity forValidity -> ShowS
[InValidOption option forInvalidity forValidity] -> ShowS
InValidOption option forInvalidity forValidity -> String
(Int -> InValidOption option forInvalidity forValidity -> ShowS)
-> (InValidOption option forInvalidity forValidity -> String)
-> ([InValidOption option forInvalidity forValidity] -> ShowS)
-> Show (InValidOption option forInvalidity forValidity)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall option forInvalidity forValidity.
(Show forInvalidity, Show forValidity, Show option) =>
Int -> InValidOption option forInvalidity forValidity -> ShowS
forall option forInvalidity forValidity.
(Show forInvalidity, Show forValidity, Show option) =>
[InValidOption option forInvalidity forValidity] -> ShowS
forall option forInvalidity forValidity.
(Show forInvalidity, Show forValidity, Show option) =>
InValidOption option forInvalidity forValidity -> String
$cshowsPrec :: forall option forInvalidity forValidity.
(Show forInvalidity, Show forValidity, Show option) =>
Int -> InValidOption option forInvalidity forValidity -> ShowS
showsPrec :: Int -> InValidOption option forInvalidity forValidity -> ShowS
$cshow :: forall option forInvalidity forValidity.
(Show forInvalidity, Show forValidity, Show option) =>
InValidOption option forInvalidity forValidity -> String
show :: InValidOption option forInvalidity forValidity -> String
$cshowList :: forall option forInvalidity forValidity.
(Show forInvalidity, Show forValidity, Show option) =>
[InValidOption option forInvalidity forValidity] -> ShowS
showList :: [InValidOption option forInvalidity forValidity] -> ShowS
Show)
mapInValidOption
:: (a -> b)
-> (c -> d)
-> (e -> f)
-> InValidOption a c e
-> InValidOption b d f
mapInValidOption :: forall a b c d e f.
(a -> b)
-> (c -> d)
-> (e -> f)
-> InValidOption a c e
-> InValidOption b d f
mapInValidOption a -> b
f c -> d
g e -> f
h InValidOption {a
Either c e
hint :: forall option forInvalidity forValidity.
InValidOption option forInvalidity forValidity
-> Either forInvalidity forValidity
option :: forall option forInvalidity forValidity.
InValidOption option forInvalidity forValidity -> option
hint :: Either c e
option :: a
..} = InValidOption {
hint :: Either d f
hint = (c -> d) -> (e -> f) -> Either c e -> Either d f
forall a b c d. (a -> b) -> (c -> d) -> Either a c -> Either b d
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap c -> d
g e -> f
h Either c e
hint,
option :: b
option = a -> b
f a
option
}
mapInValidOptionM
:: Applicative m
=> (a -> m b)
-> (c -> m d)
-> (e -> m f)
-> InValidOption a c e
-> m (InValidOption b d f)
mapInValidOptionM :: forall (m :: * -> *) a b c d e f.
Applicative m =>
(a -> m b)
-> (c -> m d)
-> (e -> m f)
-> InValidOption a c e
-> m (InValidOption b d f)
mapInValidOptionM a -> m b
f c -> m d
g e -> m f
h InValidOption {a
Either c e
hint :: forall option forInvalidity forValidity.
InValidOption option forInvalidity forValidity
-> Either forInvalidity forValidity
option :: forall option forInvalidity forValidity.
InValidOption option forInvalidity forValidity -> option
hint :: Either c e
option :: a
..} = Either d f -> b -> InValidOption b d f
forall option forInvalidity forValidity.
Either forInvalidity forValidity
-> option -> InValidOption option forInvalidity forValidity
InValidOption
(Either d f -> b -> InValidOption b d f)
-> m (Either d f) -> m (b -> InValidOption b d f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (c -> m d) -> (e -> m f) -> Either c e -> m (Either d f)
forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bimapM c -> m d
g e -> m f
h Either c e
hint
m (b -> InValidOption b d f) -> m b -> m (InValidOption b d f)
forall a b. m (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> m b
f a
option
data RepairCdConfig
= RepairCdConfig {
RepairCdConfig -> [CdMutation]
allowedCdMutations :: ![CdMutation],
RepairCdConfig -> AllowedProperties
allowedProperties :: AllowedProperties,
RepairCdConfig -> ArticlePreference
articleToUse :: ArticlePreference,
RepairCdConfig -> CdConstraints
cdConstraints :: !CdConstraints,
RepairCdConfig -> ClassConfig
classConfig :: ClassConfig,
RepairCdConfig -> CdDrawSettings
drawSettings :: !CdDrawSettings,
RepairCdConfig -> Maybe Integer
maxInstances :: Maybe Integer,
RepairCdConfig -> ObjectProperties
objectProperties :: ObjectProperties,
RepairCdConfig -> Bool
printExtendedFeedback :: Bool,
RepairCdConfig -> Bool
printSolution :: Bool,
RepairCdConfig -> Maybe Int
timeout :: Maybe Int,
RepairCdConfig -> Bool
useNames :: Bool,
:: Maybe (Map Language String)
} deriving ((forall x. RepairCdConfig -> Rep RepairCdConfig x)
-> (forall x. Rep RepairCdConfig x -> RepairCdConfig)
-> Generic RepairCdConfig
forall x. Rep RepairCdConfig x -> RepairCdConfig
forall x. RepairCdConfig -> Rep RepairCdConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RepairCdConfig -> Rep RepairCdConfig x
from :: forall x. RepairCdConfig -> Rep RepairCdConfig x
$cto :: forall x. Rep RepairCdConfig x -> RepairCdConfig
to :: forall x. Rep RepairCdConfig x -> RepairCdConfig
Generic, ReadPrec [RepairCdConfig]
ReadPrec RepairCdConfig
Int -> ReadS RepairCdConfig
ReadS [RepairCdConfig]
(Int -> ReadS RepairCdConfig)
-> ReadS [RepairCdConfig]
-> ReadPrec RepairCdConfig
-> ReadPrec [RepairCdConfig]
-> Read RepairCdConfig
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RepairCdConfig
readsPrec :: Int -> ReadS RepairCdConfig
$creadList :: ReadS [RepairCdConfig]
readList :: ReadS [RepairCdConfig]
$creadPrec :: ReadPrec RepairCdConfig
readPrec :: ReadPrec RepairCdConfig
$creadListPrec :: ReadPrec [RepairCdConfig]
readListPrec :: ReadPrec [RepairCdConfig]
Read, Int -> RepairCdConfig -> ShowS
[RepairCdConfig] -> ShowS
RepairCdConfig -> String
(Int -> RepairCdConfig -> ShowS)
-> (RepairCdConfig -> String)
-> ([RepairCdConfig] -> ShowS)
-> Show RepairCdConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RepairCdConfig -> ShowS
showsPrec :: Int -> RepairCdConfig -> ShowS
$cshow :: RepairCdConfig -> String
show :: RepairCdConfig -> String
$cshowList :: [RepairCdConfig] -> ShowS
showList :: [RepairCdConfig] -> ShowS
Show)
defaultRepairCdConfig :: RepairCdConfig
defaultRepairCdConfig :: RepairCdConfig
defaultRepairCdConfig
= RepairCdConfig {
allowedCdMutations :: [CdMutation]
allowedCdMutations = [CdMutation
AddRelationship, CdMutation
RemoveRelationship],
allowedProperties :: AllowedProperties
allowedProperties = AllowedProperties
allowNothing {
compositionCycles :: Bool
compositionCycles = Bool
True,
selfRelationships :: Bool
selfRelationships = Bool
True
},
articleToUse :: ArticlePreference
articleToUse = ArticlePreference
UseDefiniteArticleWherePossible,
cdConstraints :: CdConstraints
cdConstraints = CdConstraints
defaultCdConstraints,
classConfig :: ClassConfig
classConfig = ClassConfig {
classLimits :: (Int, Int)
classLimits = (Int
4, Int
4),
aggregationLimits :: (Int, Maybe Int)
aggregationLimits = (Int
0, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0),
associationLimits :: (Int, Maybe Int)
associationLimits = (Int
0, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1),
compositionLimits :: (Int, Maybe Int)
compositionLimits = (Int
2, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
3),
inheritanceLimits :: (Int, Maybe Int)
inheritanceLimits = (Int
0, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0),
relationshipLimits :: (Int, Maybe Int)
relationshipLimits = (Int
3, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4)
},
drawSettings :: CdDrawSettings
drawSettings = CdDrawSettings
defaultCdDrawSettings,
maxInstances :: Maybe Integer
maxInstances = Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
5,
objectProperties :: ObjectProperties
objectProperties = ObjectProperties {
anonymousObjectProportion :: Rational
anonymousObjectProportion = Integer
0 Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
1,
completelyInhabited :: Maybe Bool
completelyInhabited = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True,
hasLimitedIsolatedObjects :: Bool
hasLimitedIsolatedObjects = Bool
False,
hasSelfLoops :: Maybe Bool
hasSelfLoops = Maybe Bool
forall a. Maybe a
Nothing,
usesEveryRelationshipName :: Maybe Bool
usesEveryRelationshipName = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True
},
printExtendedFeedback :: Bool
printExtendedFeedback = Bool
True,
printSolution :: Bool
printSolution = Bool
True,
timeout :: Maybe Int
timeout = Maybe Int
forall a. Maybe a
Nothing,
useNames :: Bool
useNames = Bool
True,
extraText :: Maybe (Map Language String)
extraText = Maybe (Map Language String)
forall a. Maybe a
Nothing
}
checkRepairCdConfig :: RepairCdConfig -> Maybe String
checkRepairCdConfig :: RepairCdConfig -> Maybe String
checkRepairCdConfig RepairCdConfig {Bool
[CdMutation]
Maybe Int
Maybe Integer
Maybe (Map Language String)
ArticlePreference
AllowedProperties
ObjectProperties
CdDrawSettings
CdConstraints
ClassConfig
allowedCdMutations :: RepairCdConfig -> [CdMutation]
allowedProperties :: RepairCdConfig -> AllowedProperties
articleToUse :: RepairCdConfig -> ArticlePreference
cdConstraints :: RepairCdConfig -> CdConstraints
classConfig :: RepairCdConfig -> ClassConfig
drawSettings :: RepairCdConfig -> CdDrawSettings
maxInstances :: RepairCdConfig -> Maybe Integer
objectProperties :: RepairCdConfig -> ObjectProperties
printExtendedFeedback :: RepairCdConfig -> Bool
printSolution :: RepairCdConfig -> Bool
timeout :: RepairCdConfig -> Maybe Int
useNames :: RepairCdConfig -> Bool
extraText :: RepairCdConfig -> Maybe (Map Language String)
allowedCdMutations :: [CdMutation]
allowedProperties :: AllowedProperties
articleToUse :: ArticlePreference
cdConstraints :: CdConstraints
classConfig :: ClassConfig
drawSettings :: CdDrawSettings
maxInstances :: Maybe Integer
objectProperties :: ObjectProperties
printExtendedFeedback :: Bool
printSolution :: Bool
timeout :: Maybe Int
useNames :: Bool
extraText :: Maybe (Map Language String)
..}
| Bool -> Bool
not (CdDrawSettings -> Bool
printNames CdDrawSettings
drawSettings) Bool -> Bool -> Bool
&& Bool
useNames
= String -> Maybe String
forall a. a -> Maybe a
Just String
"use names is only possible when printing names"
| ObjectProperties -> Maybe Bool
completelyInhabited ObjectProperties
objectProperties Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
/= Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True
= String -> Maybe String
forall a. a -> Maybe a
Just String
"completelyInhabited needs to be set to 'Just True' for this task type"
| ObjectProperties -> Maybe Bool
usesEveryRelationshipName ObjectProperties
objectProperties Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
/= Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True
= String -> Maybe String
forall a. a -> Maybe a
Just [iii|
usesEveryRelationshipName needs to be set to 'Just True' for this task type
|]
| Bool
printExtendedFeedback Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
printSolution
= String -> Maybe String
forall a. a -> Maybe a
Just [iii|
printExtendedFeedback leaks the correct solution
and thus can only be enabled when printSolution is set to True
|]
| Bool
otherwise
= ClassConfig -> AllowedProperties -> Maybe String
checkClassConfigAndChanges ClassConfig
classConfig AllowedProperties
allowedProperties
Maybe String -> Maybe String -> Maybe String
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> AllowedProperties -> CdConstraints -> Maybe String
checkCdConstraints AllowedProperties
allowedProperties CdConstraints
cdConstraints
Maybe String -> Maybe String -> Maybe String
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [CdMutation] -> Maybe String
checkCdMutations [CdMutation]
allowedCdMutations
Maybe String -> Maybe String -> Maybe String
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> CdDrawSettings -> Maybe String
checkCdDrawSettings CdDrawSettings
drawSettings
Maybe String -> Maybe String -> Maybe String
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ObjectProperties -> Maybe String
checkObjectProperties ObjectProperties
objectProperties
Maybe String -> Maybe String -> Maybe String
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ClassConfig -> ObjectProperties -> Maybe String
checkClassConfigAndObjectProperties ClassConfig
classConfig ObjectProperties
objectProperties
Maybe String -> Maybe String -> Maybe String
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> CdDrawSettings -> AllowedProperties -> Maybe String
checkCdDrawProperties CdDrawSettings
drawSettings AllowedProperties
allowedProperties
checkClassConfigAndChanges
:: ClassConfig
-> AllowedProperties
-> Maybe String
checkClassConfigAndChanges :: ClassConfig -> AllowedProperties -> Maybe String
checkClassConfigAndChanges ClassConfig
classConfig AllowedProperties
allowedProperties =
ClassConfig -> Maybe String
checkClassConfig ClassConfig
classConfig
Maybe String -> Maybe String -> Maybe String
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [Maybe String] -> Maybe String
forall {a}. [Maybe a] -> Maybe a
onlyFirst ((StructuralWeakening -> Maybe String)
-> [StructuralWeakening] -> [Maybe String]
forall a b. (a -> b) -> [a] -> [b]
map StructuralWeakening -> Maybe String
checkChange ([StructuralWeakening] -> [Maybe String])
-> [StructuralWeakening] -> [Maybe String]
forall a b. (a -> b) -> a -> b
$ AllowedProperties -> [StructuralWeakening]
legalStructuralWeakenings AllowedProperties
allowedProperties)
where
checkProp :: RelationshipProperties -> Maybe String
checkProp = ClassConfig -> RelationshipProperties -> Maybe String
checkClassConfigWithProperties ClassConfig
classConfig
onlyFirst :: [Maybe a] -> Maybe a
onlyFirst = [a] -> Maybe a
forall a. [a] -> Maybe a
listToMaybe ([a] -> Maybe a) -> ([Maybe a] -> [a]) -> [Maybe a] -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe a] -> [a]
forall a. [Maybe a] -> [a]
catMaybes
checkChange :: StructuralWeakening -> Maybe String
checkChange StructuralWeakening
c =
([iii|
You should amend your class configuration for
or disable the property change "#{weakeningName c}":|] String -> ShowS
forall a. [a] -> [a] -> [a]
++)
ShowS -> Maybe String -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RelationshipProperties -> Maybe String
checkProp (StructuralWeakening -> RelationshipProperties
toProperty StructuralWeakening
c)
defaultRepairCdTaskText :: RepairCdTaskText
defaultRepairCdTaskText :: RepairCdTaskText
defaultRepairCdTaskText = [
RepairCdTaskText -> GenericOutput Language RepairCdTaskTextElement
forall language element.
[GenericOutput language element] -> GenericOutput language element
Paragraph (RepairCdTaskText
-> GenericOutput Language RepairCdTaskTextElement)
-> RepairCdTaskText
-> GenericOutput Language RepairCdTaskTextElement
forall a b. (a -> b) -> a -> b
$ GenericOutput Language RepairCdTaskTextElement -> RepairCdTaskText
forall a. a -> [a]
singleton (GenericOutput Language RepairCdTaskTextElement
-> RepairCdTaskText)
-> GenericOutput Language RepairCdTaskTextElement
-> RepairCdTaskText
forall a b. (a -> b) -> a -> b
$ Map Language String
-> GenericOutput Language RepairCdTaskTextElement
forall language element.
Map language String -> GenericOutput language element
Translated (Map Language String
-> GenericOutput Language RepairCdTaskTextElement)
-> Map Language String
-> GenericOutput Language RepairCdTaskTextElement
forall a b. (a -> b) -> a -> b
$ State (Map Language String) () -> Map Language String
forall l a. State (Map l a) () -> Map l a
translations (State (Map Language String) () -> Map Language String)
-> State (Map Language String) () -> Map Language String
forall a b. (a -> b) -> a -> b
$ do
String -> State (Map Language String) ()
english String
"Consider the following class diagram, which unfortunately is invalid:"
String -> State (Map Language String) ()
german String
"Betrachten Sie folgendes Klassendiagramm, welches leider ungültig ist:",
RepairCdTaskText -> GenericOutput Language RepairCdTaskTextElement
forall language element.
[GenericOutput language element] -> GenericOutput language element
Paragraph (RepairCdTaskText
-> GenericOutput Language RepairCdTaskTextElement)
-> RepairCdTaskText
-> GenericOutput Language RepairCdTaskTextElement
forall a b. (a -> b) -> a -> b
$ GenericOutput Language RepairCdTaskTextElement -> RepairCdTaskText
forall a. a -> [a]
singleton (GenericOutput Language RepairCdTaskTextElement
-> RepairCdTaskText)
-> GenericOutput Language RepairCdTaskTextElement
-> RepairCdTaskText
forall a b. (a -> b) -> a -> b
$ RepairCdTaskTextElement
-> GenericOutput Language RepairCdTaskTextElement
forall language element. element -> GenericOutput language element
Special RepairCdTaskTextElement
IncorrectCd,
RepairCdTaskText -> GenericOutput Language RepairCdTaskTextElement
forall language element.
[GenericOutput language element] -> GenericOutput language element
Paragraph (RepairCdTaskText
-> GenericOutput Language RepairCdTaskTextElement)
-> RepairCdTaskText
-> GenericOutput Language RepairCdTaskTextElement
forall a b. (a -> b) -> a -> b
$ GenericOutput Language RepairCdTaskTextElement -> RepairCdTaskText
forall a. a -> [a]
singleton (GenericOutput Language RepairCdTaskTextElement
-> RepairCdTaskText)
-> GenericOutput Language RepairCdTaskTextElement
-> RepairCdTaskText
forall a b. (a -> b) -> a -> b
$ Map Language String
-> GenericOutput Language RepairCdTaskTextElement
forall language element.
Map language String -> GenericOutput language element
Translated (Map Language String
-> GenericOutput Language RepairCdTaskTextElement)
-> Map Language String
-> GenericOutput Language RepairCdTaskTextElement
forall a b. (a -> b) -> a -> b
$ State (Map Language String) () -> Map Language String
forall l a. State (Map l a) () -> Map l a
translations (State (Map Language String) () -> Map Language String)
-> State (Map Language String) () -> Map Language String
forall a b. (a -> b) -> a -> b
$ do
String -> State (Map Language String) ()
english [i|Which of the following changes would each repair the class diagram?|]
String -> State (Map Language String) ()
german [i|Welche der folgenden Änderungen würden jeweils das Klassendiagramm reparieren?|],
RepairCdTaskTextElement
-> GenericOutput Language RepairCdTaskTextElement
forall language element. element -> GenericOutput language element
Special RepairCdTaskTextElement
PotentialFixes,
RepairCdTaskText -> GenericOutput Language RepairCdTaskTextElement
forall language element.
[GenericOutput language element] -> GenericOutput language element
Paragraph (RepairCdTaskText
-> GenericOutput Language RepairCdTaskTextElement)
-> RepairCdTaskText
-> GenericOutput Language RepairCdTaskTextElement
forall a b. (a -> b) -> a -> b
$ GenericOutput Language RepairCdTaskTextElement -> RepairCdTaskText
forall a. a -> [a]
singleton (GenericOutput Language RepairCdTaskTextElement
-> RepairCdTaskText)
-> GenericOutput Language RepairCdTaskTextElement
-> RepairCdTaskText
forall a b. (a -> b) -> a -> b
$ Map Language String
-> GenericOutput Language RepairCdTaskTextElement
forall language element.
Map language String -> GenericOutput language element
Translated (Map Language String
-> GenericOutput Language RepairCdTaskTextElement)
-> Map Language String
-> GenericOutput Language RepairCdTaskTextElement
forall a b. (a -> b) -> a -> b
$ State (Map Language String) () -> Map Language String
forall l a. State (Map l a) () -> Map l a
translations (State (Map Language String) () -> Map Language String)
-> State (Map Language String) () -> Map Language String
forall a b. (a -> b) -> a -> b
$ do
String -> State (Map Language String) ()
english [i|Please state your answer by giving a list of numbers, indicating all changes each resulting in a valid class diagram.|]
String -> State (Map Language String) ()
german [i|Bitte geben Sie Ihre Antwort als Liste aller Zahlen an, deren Änderungen jeweils in einem gültigen Klassendiagramm resultieren.|],
RepairCdTaskText -> GenericOutput Language RepairCdTaskTextElement
forall language element.
[GenericOutput language element] -> GenericOutput language element
Paragraph [
Map Language String
-> GenericOutput Language RepairCdTaskTextElement
forall language element.
Map language String -> GenericOutput language element
Translated (Map Language String
-> GenericOutput Language RepairCdTaskTextElement)
-> Map Language String
-> GenericOutput Language RepairCdTaskTextElement
forall a b. (a -> b) -> a -> b
$ State (Map Language String) () -> Map Language String
forall l a. State (Map l a) () -> Map l a
translations (State (Map Language String) () -> Map Language String)
-> State (Map Language String) () -> Map Language String
forall a b. (a -> b) -> a -> b
$ do
String -> State (Map Language String) ()
english [i|Answer by giving a comma separated list of all appropriate options, e.g., |]
String -> State (Map Language String) ()
german [i|Antworten Sie durch Angabe einer durch Komma separierten Liste aller zutreffenden Optionen. Zum Beispiel |],
Map Language String
-> GenericOutput Language RepairCdTaskTextElement
forall language element.
Map language String -> GenericOutput language element
Code (Map Language String
-> GenericOutput Language RepairCdTaskTextElement)
-> Map Language String
-> GenericOutput Language RepairCdTaskTextElement
forall a b. (a -> b) -> a -> b
$ String -> Map Language String
forall a. a -> Map Language a
uniform String
"[1, 2]",
Map Language String
-> GenericOutput Language RepairCdTaskTextElement
forall language element.
Map language String -> GenericOutput language element
Translated (Map Language String
-> GenericOutput Language RepairCdTaskTextElement)
-> Map Language String
-> GenericOutput Language RepairCdTaskTextElement
forall a b. (a -> b) -> a -> b
$ State (Map Language String) () -> Map Language String
forall l a. State (Map l a) () -> Map l a
translations (State (Map Language String) () -> Map Language String)
-> State (Map Language String) () -> Map Language String
forall a b. (a -> b) -> a -> b
$ do
String -> State (Map Language String) ()
english [i| would indicate that options 1 and 2 each repair the given class diagram.|]
String -> State (Map Language String) ()
german [i| als Angabe würde bedeuten, dass die Optionen 1 und 2 jeweils das gegebene Klassendiagramm reparieren.|]
]
]
repairCdTask
:: (MonadCache m, MonadDiagrams m, MonadGraphviz m, OutputCapable m)
=> FilePath
-> RepairCdInstance
-> LangM m
repairCdTask :: forall (m :: * -> *).
(MonadCache m, MonadDiagrams m, MonadGraphviz m,
OutputCapable m) =>
String -> RepairCdInstance -> LangM m
repairCdTask String
path RepairCdInstance
task = do
String -> RepairCdInstance -> LangM m
forall (m :: * -> *).
(MonadCache m, MonadDiagrams m, MonadGraphviz m,
OutputCapable m) =>
String -> RepairCdInstance -> LangM m
toTaskText String
path RepairCdInstance
task
LangM m -> LangM m
forall l (m :: * -> *).
GenericOutputCapable l m =>
GenericLangM l m () -> GenericLangM l m ()
paragraph LangM m
forall (m :: * -> *). OutputCapable m => LangM m
simplifiedInformation
LangM m -> LangM m
forall l (m :: * -> *).
GenericOutputCapable l m =>
GenericLangM l m () -> GenericLangM l m ()
paragraph LangM m
forall (m :: * -> *). OutputCapable m => LangM m
hoveringInformation
Maybe (Map Language String) -> LangM m
forall (m :: * -> *).
OutputCapable m =>
Maybe (Map Language String) -> LangM m
extra (Maybe (Map Language String) -> LangM m)
-> Maybe (Map Language String) -> LangM m
forall a b. (a -> b) -> a -> b
$ RepairCdInstance -> Maybe (Map Language String)
addText RepairCdInstance
task
pure ()
repairCdSyntax :: OutputCapable m => RepairCdInstance -> [Int] -> LangM m
repairCdSyntax :: forall (m :: * -> *).
OutputCapable m =>
RepairCdInstance -> [Int] -> LangM m
repairCdSyntax RepairCdInstance
inst =
Bool -> [Int] -> [Int] -> LangM m
forall (m :: * -> *) a.
(OutputCapable m, Ord a, Show a) =>
Bool -> [a] -> [a] -> LangM m
multipleChoiceSyntax Bool
False (Map Int RelationshipChange -> [Int]
forall k a. Map k a -> [k]
M.keys (Map Int RelationshipChange -> [Int])
-> Map Int RelationshipChange -> [Int]
forall a b. (a -> b) -> a -> b
$ RepairCdInstance -> Map Int RelationshipChange
changes RepairCdInstance
inst)
repairCdEvaluation
:: (Alternative m, MonadCache m, MonadDiagrams m, MonadGraphviz m, OutputCapable m)
=> FilePath
-> RepairCdInstance
-> [Int]
-> Rated m
repairCdEvaluation :: forall (m :: * -> *).
(Alternative m, MonadCache m, MonadDiagrams m, MonadGraphviz m,
OutputCapable m) =>
String -> RepairCdInstance -> [Int] -> Rated m
repairCdEvaluation String
path RepairCdInstance
inst [Int]
xs = LangM' m Rational -> LangM' m Rational
forall (m :: * -> *) a. OutputCapable m => LangM' m a -> LangM' m a
addPretext (LangM' m Rational -> LangM' m Rational)
-> LangM' m Rational -> LangM' m Rational
forall a b. (a -> b) -> a -> b
$ do
let chs :: Map Language String
chs = [(Language, String)] -> Map Language String
forall k a. Eq k => [(k, a)] -> Map k a
M.fromAscList [
(Language
English, String
"repairs"),
(Language
German, String
"Reparaturen")
]
solution :: Map Int Bool
solution = Either AnyCd Cd -> Bool
forall a b. Either a b -> Bool
isRight (Either AnyCd Cd -> Bool)
-> (RelationshipChange -> Either AnyCd Cd)
-> RelationshipChange
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RelationshipChange -> Either AnyCd Cd
forall option forInvalidity forValidity.
InValidOption option forInvalidity forValidity
-> Either forInvalidity forValidity
hint (RelationshipChange -> Bool)
-> Map Int RelationshipChange -> Map Int Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RepairCdInstance -> Map Int RelationshipChange
changes RepairCdInstance
inst
correctAnswer :: Maybe String
correctAnswer
| RepairCdInstance -> Bool
showSolution RepairCdInstance
inst = String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> String -> Maybe String
forall a b. (a -> b) -> a -> b
$ [Int] -> String
forall a. Show a => a -> String
show ([Int] -> String) -> [Int] -> String
forall a b. (a -> b) -> a -> b
$ RepairCdInstance -> [Int]
repairCdSolution RepairCdInstance
inst
| Bool
otherwise = Maybe String
forall a. Maybe a
Nothing
LangM' m Rational -> LangM m -> LangM' m Rational
forall (m :: * -> *).
(Alternative m, Monad m, OutputCapable m) =>
Rated m -> LangM m -> Rated m
reRefuse
(ArticleToUse
-> Map Language String
-> Maybe String
-> Map Int Bool
-> [Int]
-> LangM' m Rational
forall (m :: * -> *) a.
(OutputCapable m, Ord a) =>
ArticleToUse
-> Map Language String
-> Maybe String
-> Map a Bool
-> [a]
-> Rated m
multipleChoice ArticleToUse
DefiniteArticle Map Language String
chs Maybe String
correctAnswer Map Int Bool
solution [Int]
xs)
(LangM m -> LangM' m Rational) -> LangM m -> LangM' m Rational
forall a b. (a -> b) -> a -> b
$ Bool -> LangM m -> LangM m
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (RepairCdInstance -> Bool
showExtendedFeedback RepairCdInstance
inst)
(LangM m -> LangM m) -> LangM m -> LangM m
forall a b. (a -> b) -> a -> b
$ GenericLangM Language m (Map Int ()) -> LangM m
forall (f :: * -> *) a. Functor f => f a -> f ()
void (GenericLangM Language m (Map Int ()) -> LangM m)
-> GenericLangM Language m (Map Int ()) -> LangM m
forall a b. (a -> b) -> a -> b
$ (Int -> RelationshipChange -> LangM m)
-> Map Int RelationshipChange
-> GenericLangM Language m (Map Int ())
forall (t :: * -> *) k a b.
Applicative t =>
(k -> a -> t b) -> Map k a -> t (Map k b)
M.traverseWithKey
(String
-> CdDrawSettings -> [Int] -> Int -> RelationshipChange -> LangM m
forall (m :: * -> *).
(MonadCache m, MonadDiagrams m, MonadGraphviz m,
OutputCapable m) =>
String
-> CdDrawSettings -> [Int] -> Int -> RelationshipChange -> LangM m
repairCdFeedback String
path (RepairCdInstance -> CdDrawSettings
cdDrawSettings RepairCdInstance
inst) [Int]
xs)
(RepairCdInstance -> Map Int RelationshipChange
changes RepairCdInstance
inst)
repairCdFeedback
:: (MonadCache m, MonadDiagrams m, MonadGraphviz m, OutputCapable m)
=> FilePath
-> CdDrawSettings
-> [Int]
-> Int
-> RelationshipChange
-> LangM m
repairCdFeedback :: forall (m :: * -> *).
(MonadCache m, MonadDiagrams m, MonadGraphviz m,
OutputCapable m) =>
String
-> CdDrawSettings -> [Int] -> Int -> RelationshipChange -> LangM m
repairCdFeedback String
path CdDrawSettings
drawSettings [Int]
xs Int
x RelationshipChange
cdChange =
case RelationshipChange -> Either AnyCd Cd
forall option forInvalidity forValidity.
InValidOption option forInvalidity forValidity
-> Either forInvalidity forValidity
hint RelationshipChange
cdChange of
Left AnyCd
cd
| Int
x Int -> [Int] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Int]
xs -> LangM m
notCorrect LangM m -> LangM m -> LangM m
forall a b.
GenericLangM Language m a
-> GenericLangM Language m b -> GenericLangM Language m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LangM m
makesIncorrect LangM m -> LangM m -> LangM m
forall a b.
GenericLangM Language m a
-> GenericLangM Language m b -> GenericLangM Language m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> AnyCd -> LangM m
forall {l} {m :: * -> *}.
(GenericOutputCapable l m, MonadCache m, MonadDiagrams m,
MonadGraphviz m) =>
AnyCd -> GenericLangM l m ()
showCd AnyCd
cd
| Bool
otherwise -> LangM m
correct LangM m -> LangM m -> LangM m
forall a b.
GenericLangM Language m a
-> GenericLangM Language m b -> GenericLangM Language m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LangM m
makesIncorrect LangM m -> LangM m -> LangM m
forall a b.
GenericLangM Language m a
-> GenericLangM Language m b -> GenericLangM Language m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> AnyCd -> LangM m
forall {l} {m :: * -> *}.
(GenericOutputCapable l m, MonadCache m, MonadDiagrams m,
MonadGraphviz m) =>
AnyCd -> GenericLangM l m ()
showCd AnyCd
cd
Right Cd
cd
| Int
x Int -> [Int] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Int]
xs -> LangM m
correct LangM m -> LangM m -> LangM m
forall a b.
GenericLangM Language m a
-> GenericLangM Language m b -> GenericLangM Language m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LangM m
makesCorrect LangM m -> LangM m -> LangM m
forall a b.
GenericLangM Language m a
-> GenericLangM Language m b -> GenericLangM Language m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> AnyCd -> LangM m
forall {l} {m :: * -> *}.
(GenericOutputCapable l m, MonadCache m, MonadDiagrams m,
MonadGraphviz m) =>
AnyCd -> GenericLangM l m ()
showCd (Cd -> AnyCd
forall className relationshipName.
ClassDiagram className relationshipName
-> AnyClassDiagram className relationshipName
fromClassDiagram Cd
cd)
| Bool
otherwise -> LangM m
notCorrect LangM m -> LangM m -> LangM m
forall a b.
GenericLangM Language m a
-> GenericLangM Language m b -> GenericLangM Language m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LangM m
makesCorrect LangM m -> LangM m -> LangM m
forall a b.
GenericLangM Language m a
-> GenericLangM Language m b -> GenericLangM Language m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> AnyCd -> LangM m
forall {l} {m :: * -> *}.
(GenericOutputCapable l m, MonadCache m, MonadDiagrams m,
MonadGraphviz m) =>
AnyCd -> GenericLangM l m ()
showCd (Cd -> AnyCd
forall className relationshipName.
ClassDiagram className relationshipName
-> AnyClassDiagram className relationshipName
fromClassDiagram Cd
cd)
where
correct :: LangM m
correct = LangM m -> LangM m
forall l (m :: * -> *).
GenericOutputCapable l m =>
GenericLangM l m () -> GenericLangM l m ()
paragraph (LangM m -> LangM m) -> LangM m -> LangM m
forall a b. (a -> b) -> a -> b
$ State (Map Language String) () -> LangM m
forall l (m :: * -> *).
GenericOutputCapable l m =>
State (Map l String) () -> GenericLangM l m ()
translate (State (Map Language String) () -> LangM m)
-> State (Map Language String) () -> LangM m
forall a b. (a -> b) -> a -> b
$ do
String -> State (Map Language String) ()
english [iii|Your answer about change #{x} is correct.|]
String -> State (Map Language String) ()
german [iii|Ihre Antwort zu Änderung #{x} ist richtig.|]
notCorrect :: LangM m
notCorrect = LangM m -> LangM m
forall l (m :: * -> *).
GenericOutputCapable l m =>
GenericLangM l m () -> GenericLangM l m ()
paragraph (LangM m -> LangM m) -> LangM m -> LangM m
forall a b. (a -> b) -> a -> b
$ State (Map Language String) () -> LangM m
forall l (m :: * -> *).
GenericOutputCapable l m =>
State (Map l String) () -> GenericLangM l m ()
translate (State (Map Language String) () -> LangM m)
-> State (Map Language String) () -> LangM m
forall a b. (a -> b) -> a -> b
$ do
String -> State (Map Language String) ()
english [iii|Your answer about change #{x} is not correct.|]
String -> State (Map Language String) ()
german [iii|Ihre Antwort zu Änderung #{x} ist nicht richtig.|]
makesCorrect :: LangM m
makesCorrect = LangM m -> LangM m
forall l (m :: * -> *).
GenericOutputCapable l m =>
GenericLangM l m () -> GenericLangM l m ()
paragraph (LangM m -> LangM m) -> LangM m -> LangM m
forall a b. (a -> b) -> a -> b
$ State (Map Language String) () -> LangM m
forall l (m :: * -> *).
GenericOutputCapable l m =>
State (Map l String) () -> GenericLangM l m ()
translate (State (Map Language String) () -> LangM m)
-> State (Map Language String) () -> LangM m
forall a b. (a -> b) -> a -> b
$ do
String -> State (Map Language String) ()
english [iii|The change repairs the class diagram as it results in:|]
String -> State (Map Language String) ()
german [iii|
Die Änderung repariert das Klassendiagramm, da es dann so aussieht:
|]
makesIncorrect :: LangM m
makesIncorrect = LangM m -> LangM m
forall l (m :: * -> *).
GenericOutputCapable l m =>
GenericLangM l m () -> GenericLangM l m ()
paragraph (LangM m -> LangM m) -> LangM m -> LangM m
forall a b. (a -> b) -> a -> b
$ State (Map Language String) () -> LangM m
forall l (m :: * -> *).
GenericOutputCapable l m =>
State (Map l String) () -> GenericLangM l m ()
translate (State (Map Language String) () -> LangM m)
-> State (Map Language String) () -> LangM m
forall a b. (a -> b) -> a -> b
$ do
String -> State (Map Language String) ()
english [iii|The change does not repair the class diagram as it results in:|]
String -> State (Map Language String) ()
german [iii|
Die Änderung repariert das Klassendiagramm nicht, da es dann so aussieht:
|]
showCd :: AnyCd -> GenericLangM l m ()
showCd AnyCd
cd = GenericLangM l m () -> GenericLangM l m ()
forall l (m :: * -> *).
GenericOutputCapable l m =>
GenericLangM l m () -> GenericLangM l m ()
paragraph (GenericLangM l m () -> GenericLangM l m ())
-> GenericLangM l m () -> GenericLangM l m ()
forall a b. (a -> b) -> a -> b
$
String -> GenericLangM l m ()
forall l (m :: * -> *).
GenericOutputCapable l m =>
String -> GenericLangM l m ()
image (String -> GenericLangM l m ()) -> m String -> GenericLangM l m ()
forall (m :: * -> *) a l b.
Monad m =>
(a -> GenericLangM l m b) -> m a -> GenericLangM l m b
$=<< CdDrawSettings -> Style V2 Double -> AnyCd -> String -> m String
forall (m :: * -> *).
(MonadCache m, MonadDiagrams m, MonadGraphviz m) =>
CdDrawSettings -> Style V2 Double -> AnyCd -> String -> m String
cacheCd CdDrawSettings
drawSettings Style V2 Double
forall a. Monoid a => a
mempty AnyCd
cd String
path
repairCdSolution :: RepairCdInstance -> [Int]
repairCdSolution :: RepairCdInstance -> [Int]
repairCdSolution = Map Int Bool -> [Int]
forall k a. Map k a -> [k]
M.keys (Map Int Bool -> [Int])
-> (RepairCdInstance -> Map Int Bool) -> RepairCdInstance -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Bool) -> Map Int Bool -> Map Int Bool
forall a k. (a -> Bool) -> Map k a -> Map k a
M.filter Bool -> Bool
forall a. a -> a
id (Map Int Bool -> Map Int Bool)
-> (RepairCdInstance -> Map Int Bool)
-> RepairCdInstance
-> Map Int Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (RelationshipChange -> Bool)
-> Map Int RelationshipChange -> Map Int Bool
forall a b. (a -> b) -> Map Int a -> Map Int b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Either AnyCd Cd -> Bool
forall a b. Either a b -> Bool
isRight (Either AnyCd Cd -> Bool)
-> (RelationshipChange -> Either AnyCd Cd)
-> RelationshipChange
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RelationshipChange -> Either AnyCd Cd
forall option forInvalidity forValidity.
InValidOption option forInvalidity forValidity
-> Either forInvalidity forValidity
hint) (Map Int RelationshipChange -> Map Int Bool)
-> (RepairCdInstance -> Map Int RelationshipChange)
-> RepairCdInstance
-> Map Int Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RepairCdInstance -> Map Int RelationshipChange
changes
type RepairCdTaskText = [SpecialOutput RepairCdTaskTextElement]
data RepairCdTaskTextElement
= IncorrectCd
| PotentialFixes
deriving (RepairCdTaskTextElement
RepairCdTaskTextElement
-> RepairCdTaskTextElement -> Bounded RepairCdTaskTextElement
forall a. a -> a -> Bounded a
$cminBound :: RepairCdTaskTextElement
minBound :: RepairCdTaskTextElement
$cmaxBound :: RepairCdTaskTextElement
maxBound :: RepairCdTaskTextElement
Bounded, Int -> RepairCdTaskTextElement
RepairCdTaskTextElement -> Int
RepairCdTaskTextElement -> [RepairCdTaskTextElement]
RepairCdTaskTextElement -> RepairCdTaskTextElement
RepairCdTaskTextElement
-> RepairCdTaskTextElement -> [RepairCdTaskTextElement]
RepairCdTaskTextElement
-> RepairCdTaskTextElement
-> RepairCdTaskTextElement
-> [RepairCdTaskTextElement]
(RepairCdTaskTextElement -> RepairCdTaskTextElement)
-> (RepairCdTaskTextElement -> RepairCdTaskTextElement)
-> (Int -> RepairCdTaskTextElement)
-> (RepairCdTaskTextElement -> Int)
-> (RepairCdTaskTextElement -> [RepairCdTaskTextElement])
-> (RepairCdTaskTextElement
-> RepairCdTaskTextElement -> [RepairCdTaskTextElement])
-> (RepairCdTaskTextElement
-> RepairCdTaskTextElement -> [RepairCdTaskTextElement])
-> (RepairCdTaskTextElement
-> RepairCdTaskTextElement
-> RepairCdTaskTextElement
-> [RepairCdTaskTextElement])
-> Enum RepairCdTaskTextElement
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: RepairCdTaskTextElement -> RepairCdTaskTextElement
succ :: RepairCdTaskTextElement -> RepairCdTaskTextElement
$cpred :: RepairCdTaskTextElement -> RepairCdTaskTextElement
pred :: RepairCdTaskTextElement -> RepairCdTaskTextElement
$ctoEnum :: Int -> RepairCdTaskTextElement
toEnum :: Int -> RepairCdTaskTextElement
$cfromEnum :: RepairCdTaskTextElement -> Int
fromEnum :: RepairCdTaskTextElement -> Int
$cenumFrom :: RepairCdTaskTextElement -> [RepairCdTaskTextElement]
enumFrom :: RepairCdTaskTextElement -> [RepairCdTaskTextElement]
$cenumFromThen :: RepairCdTaskTextElement
-> RepairCdTaskTextElement -> [RepairCdTaskTextElement]
enumFromThen :: RepairCdTaskTextElement
-> RepairCdTaskTextElement -> [RepairCdTaskTextElement]
$cenumFromTo :: RepairCdTaskTextElement
-> RepairCdTaskTextElement -> [RepairCdTaskTextElement]
enumFromTo :: RepairCdTaskTextElement
-> RepairCdTaskTextElement -> [RepairCdTaskTextElement]
$cenumFromThenTo :: RepairCdTaskTextElement
-> RepairCdTaskTextElement
-> RepairCdTaskTextElement
-> [RepairCdTaskTextElement]
enumFromThenTo :: RepairCdTaskTextElement
-> RepairCdTaskTextElement
-> RepairCdTaskTextElement
-> [RepairCdTaskTextElement]
Enum, RepairCdTaskTextElement -> RepairCdTaskTextElement -> Bool
(RepairCdTaskTextElement -> RepairCdTaskTextElement -> Bool)
-> (RepairCdTaskTextElement -> RepairCdTaskTextElement -> Bool)
-> Eq RepairCdTaskTextElement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RepairCdTaskTextElement -> RepairCdTaskTextElement -> Bool
== :: RepairCdTaskTextElement -> RepairCdTaskTextElement -> Bool
$c/= :: RepairCdTaskTextElement -> RepairCdTaskTextElement -> Bool
/= :: RepairCdTaskTextElement -> RepairCdTaskTextElement -> Bool
Eq, (forall x.
RepairCdTaskTextElement -> Rep RepairCdTaskTextElement x)
-> (forall x.
Rep RepairCdTaskTextElement x -> RepairCdTaskTextElement)
-> Generic RepairCdTaskTextElement
forall x. Rep RepairCdTaskTextElement x -> RepairCdTaskTextElement
forall x. RepairCdTaskTextElement -> Rep RepairCdTaskTextElement x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RepairCdTaskTextElement -> Rep RepairCdTaskTextElement x
from :: forall x. RepairCdTaskTextElement -> Rep RepairCdTaskTextElement x
$cto :: forall x. Rep RepairCdTaskTextElement x -> RepairCdTaskTextElement
to :: forall x. Rep RepairCdTaskTextElement x -> RepairCdTaskTextElement
Generic, Eq RepairCdTaskTextElement
Eq RepairCdTaskTextElement
-> (RepairCdTaskTextElement -> RepairCdTaskTextElement -> Ordering)
-> (RepairCdTaskTextElement -> RepairCdTaskTextElement -> Bool)
-> (RepairCdTaskTextElement -> RepairCdTaskTextElement -> Bool)
-> (RepairCdTaskTextElement -> RepairCdTaskTextElement -> Bool)
-> (RepairCdTaskTextElement -> RepairCdTaskTextElement -> Bool)
-> (RepairCdTaskTextElement
-> RepairCdTaskTextElement -> RepairCdTaskTextElement)
-> (RepairCdTaskTextElement
-> RepairCdTaskTextElement -> RepairCdTaskTextElement)
-> Ord RepairCdTaskTextElement
RepairCdTaskTextElement -> RepairCdTaskTextElement -> Bool
RepairCdTaskTextElement -> RepairCdTaskTextElement -> Ordering
RepairCdTaskTextElement
-> RepairCdTaskTextElement -> RepairCdTaskTextElement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RepairCdTaskTextElement -> RepairCdTaskTextElement -> Ordering
compare :: RepairCdTaskTextElement -> RepairCdTaskTextElement -> Ordering
$c< :: RepairCdTaskTextElement -> RepairCdTaskTextElement -> Bool
< :: RepairCdTaskTextElement -> RepairCdTaskTextElement -> Bool
$c<= :: RepairCdTaskTextElement -> RepairCdTaskTextElement -> Bool
<= :: RepairCdTaskTextElement -> RepairCdTaskTextElement -> Bool
$c> :: RepairCdTaskTextElement -> RepairCdTaskTextElement -> Bool
> :: RepairCdTaskTextElement -> RepairCdTaskTextElement -> Bool
$c>= :: RepairCdTaskTextElement -> RepairCdTaskTextElement -> Bool
>= :: RepairCdTaskTextElement -> RepairCdTaskTextElement -> Bool
$cmax :: RepairCdTaskTextElement
-> RepairCdTaskTextElement -> RepairCdTaskTextElement
max :: RepairCdTaskTextElement
-> RepairCdTaskTextElement -> RepairCdTaskTextElement
$cmin :: RepairCdTaskTextElement
-> RepairCdTaskTextElement -> RepairCdTaskTextElement
min :: RepairCdTaskTextElement
-> RepairCdTaskTextElement -> RepairCdTaskTextElement
Ord, ReadPrec [RepairCdTaskTextElement]
ReadPrec RepairCdTaskTextElement
Int -> ReadS RepairCdTaskTextElement
ReadS [RepairCdTaskTextElement]
(Int -> ReadS RepairCdTaskTextElement)
-> ReadS [RepairCdTaskTextElement]
-> ReadPrec RepairCdTaskTextElement
-> ReadPrec [RepairCdTaskTextElement]
-> Read RepairCdTaskTextElement
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RepairCdTaskTextElement
readsPrec :: Int -> ReadS RepairCdTaskTextElement
$creadList :: ReadS [RepairCdTaskTextElement]
readList :: ReadS [RepairCdTaskTextElement]
$creadPrec :: ReadPrec RepairCdTaskTextElement
readPrec :: ReadPrec RepairCdTaskTextElement
$creadListPrec :: ReadPrec [RepairCdTaskTextElement]
readListPrec :: ReadPrec [RepairCdTaskTextElement]
Read, Int -> RepairCdTaskTextElement -> ShowS
[RepairCdTaskTextElement] -> ShowS
RepairCdTaskTextElement -> String
(Int -> RepairCdTaskTextElement -> ShowS)
-> (RepairCdTaskTextElement -> String)
-> ([RepairCdTaskTextElement] -> ShowS)
-> Show RepairCdTaskTextElement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RepairCdTaskTextElement -> ShowS
showsPrec :: Int -> RepairCdTaskTextElement -> ShowS
$cshow :: RepairCdTaskTextElement -> String
show :: RepairCdTaskTextElement -> String
$cshowList :: [RepairCdTaskTextElement] -> ShowS
showList :: [RepairCdTaskTextElement] -> ShowS
Show)
toTaskText
:: (MonadCache m, MonadDiagrams m, MonadGraphviz m, OutputCapable m)
=> FilePath
-> RepairCdInstance
-> LangM m
toTaskText :: forall (m :: * -> *).
(MonadCache m, MonadDiagrams m, MonadGraphviz m,
OutputCapable m) =>
String -> RepairCdInstance -> LangM m
toTaskText String
path RepairCdInstance
task =
(RepairCdTaskTextElement -> LangM m) -> RepairCdTaskText -> LangM m
forall (m :: * -> *) element.
OutputCapable m =>
(element -> LangM m) -> [SpecialOutput element] -> LangM m
specialToOutputCapable (String -> RepairCdInstance -> RepairCdTaskTextElement -> LangM m
forall (m :: * -> *).
(MonadCache m, MonadDiagrams m, MonadGraphviz m,
OutputCapable m) =>
String -> RepairCdInstance -> RepairCdTaskTextElement -> LangM m
toTaskSpecificText String
path RepairCdInstance
task) (RepairCdInstance -> RepairCdTaskText
taskText RepairCdInstance
task)
toTaskSpecificText
:: (MonadCache m, MonadDiagrams m, MonadGraphviz m, OutputCapable m)
=> FilePath
-> RepairCdInstance
-> RepairCdTaskTextElement
-> LangM m
toTaskSpecificText :: forall (m :: * -> *).
(MonadCache m, MonadDiagrams m, MonadGraphviz m,
OutputCapable m) =>
String -> RepairCdInstance -> RepairCdTaskTextElement -> LangM m
toTaskSpecificText String
path RepairCdInstance {Bool
RepairCdTaskText
Maybe (Map Language String)
Map Int RelationshipChange
AnyCd
CdDrawSettings
addText :: RepairCdInstance -> Maybe (Map Language String)
changes :: RepairCdInstance -> Map Int RelationshipChange
showSolution :: RepairCdInstance -> Bool
showExtendedFeedback :: RepairCdInstance -> Bool
cdDrawSettings :: RepairCdInstance -> CdDrawSettings
taskText :: RepairCdInstance -> RepairCdTaskText
byName :: Bool
cdDrawSettings :: CdDrawSettings
changes :: Map Int RelationshipChange
classDiagram :: AnyCd
showExtendedFeedback :: Bool
showSolution :: Bool
taskText :: RepairCdTaskText
addText :: Maybe (Map Language String)
byName :: RepairCdInstance -> Bool
classDiagram :: RepairCdInstance -> AnyCd
..} = \case
RepairCdTaskTextElement
IncorrectCd -> String -> LangM m
forall l (m :: * -> *).
GenericOutputCapable l m =>
String -> GenericLangM l m ()
image (String -> LangM m) -> m String -> LangM m
forall (m :: * -> *) a l b.
Monad m =>
(a -> GenericLangM l m b) -> m a -> GenericLangM l m b
$=<< CdDrawSettings -> Style V2 Double -> AnyCd -> String -> m String
forall (m :: * -> *).
(MonadCache m, MonadDiagrams m, MonadGraphviz m) =>
CdDrawSettings -> Style V2 Double -> AnyCd -> String -> m String
cacheCd
CdDrawSettings
cdDrawSettings
Style V2 Double
forall a. Monoid a => a
mempty
AnyCd
classDiagram
String
path
RepairCdTaskTextElement
PotentialFixes ->
(Int -> LangM m) -> [(Int, LangM m)] -> LangM m
forall a. (a -> LangM m) -> [(a, LangM m)] -> LangM m
forall l (m :: * -> *) a.
GenericOutputCapable l m =>
(a -> GenericLangM l m ())
-> [(a, GenericLangM l m ())] -> GenericLangM l m ()
enumerateM (String -> LangM m
forall l (m :: * -> *).
GenericOutputCapable l m =>
String -> GenericLangM l m ()
text (String -> LangM m) -> (Int -> String) -> Int -> LangM m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show)
([(Int, LangM m)] -> LangM m) -> [(Int, LangM m)] -> LangM m
forall a b. (a -> b) -> a -> b
$ ((Int, RelationshipChange) -> (Int, LangM m))
-> [(Int, RelationshipChange)] -> [(Int, LangM m)]
forall a b. (a -> b) -> [a] -> [b]
map ((RelationshipChange -> LangM m)
-> (Int, RelationshipChange) -> (Int, LangM m)
forall b c a. (b -> c) -> (a, b) -> (a, c)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (Bool
-> Bool
-> Annotation ArticleToUse (Change (AnyRelationship String String))
-> LangM m
forall {m :: * -> *}.
GenericOutputCapable Language m =>
Bool
-> Bool
-> Annotation ArticleToUse (Change (AnyRelationship String String))
-> GenericLangM Language m ()
phrase Bool
byName (CdDrawSettings -> Bool
printNavigations CdDrawSettings
cdDrawSettings) (Annotation ArticleToUse (Change (AnyRelationship String String))
-> LangM m)
-> (RelationshipChange
-> Annotation
ArticleToUse (Change (AnyRelationship String String)))
-> RelationshipChange
-> LangM m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RelationshipChange
-> Annotation ArticleToUse (Change (AnyRelationship String String))
forall option forInvalidity forValidity.
InValidOption option forInvalidity forValidity -> option
option))
([(Int, RelationshipChange)] -> [(Int, LangM m)])
-> [(Int, RelationshipChange)] -> [(Int, LangM m)]
forall a b. (a -> b) -> a -> b
$ Map Int RelationshipChange -> [(Int, RelationshipChange)]
forall k a. Map k a -> [(k, a)]
M.toList Map Int RelationshipChange
changes
where
defaults :: OmittedDefaultMultiplicities
defaults = CdDrawSettings -> OmittedDefaultMultiplicities
omittedDefaults CdDrawSettings
cdDrawSettings
phrase :: Bool
-> Bool
-> Annotation ArticleToUse (Change (AnyRelationship String String))
-> GenericLangM Language m ()
phrase Bool
x Bool
y Annotation {ArticleToUse
Change (AnyRelationship String String)
annotated :: Change (AnyRelationship String String)
annotation :: ArticleToUse
annotated :: forall annotation annotated.
Annotation annotation annotated -> annotated
annotation :: forall annotation annotated.
Annotation annotation annotated -> annotation
..} = State (Map Language String) () -> GenericLangM Language m ()
forall l (m :: * -> *).
GenericOutputCapable l m =>
State (Map l String) () -> GenericLangM l m ()
translate (State (Map Language String) () -> GenericLangM Language m ())
-> State (Map Language String) () -> GenericLangM Language m ()
forall a b. (a -> b) -> a -> b
$ do
String -> State (Map Language String) ()
english (String -> State (Map Language String) ())
-> String -> State (Map Language String) ()
forall a b. (a -> b) -> a -> b
$ Language
-> OmittedDefaultMultiplicities
-> ArticleToUse
-> Bool
-> Bool
-> Change (AnyRelationship String String)
-> String
phraseChange Language
English OmittedDefaultMultiplicities
defaults ArticleToUse
annotation Bool
x Bool
y Change (AnyRelationship String String)
annotated
String -> State (Map Language String) ()
german (String -> State (Map Language String) ())
-> String -> State (Map Language String) ()
forall a b. (a -> b) -> a -> b
$ Language
-> OmittedDefaultMultiplicities
-> ArticleToUse
-> Bool
-> Bool
-> Change (AnyRelationship String String)
-> String
phraseChange Language
German OmittedDefaultMultiplicities
defaults ArticleToUse
annotation Bool
x Bool
y Change (AnyRelationship String String)
annotated
data RepairCdInstance
= RepairCdInstance {
RepairCdInstance -> Bool
byName :: !Bool,
RepairCdInstance -> CdDrawSettings
cdDrawSettings :: !CdDrawSettings,
RepairCdInstance -> Map Int RelationshipChange
changes :: Map Int RelationshipChange,
RepairCdInstance -> AnyCd
classDiagram :: AnyCd,
RepairCdInstance -> Bool
showExtendedFeedback :: Bool,
RepairCdInstance -> Bool
showSolution :: !Bool,
RepairCdInstance -> RepairCdTaskText
taskText :: !RepairCdTaskText,
RepairCdInstance -> Maybe (Map Language String)
addText :: Maybe (Map Language String)
} deriving (RepairCdInstance -> RepairCdInstance -> Bool
(RepairCdInstance -> RepairCdInstance -> Bool)
-> (RepairCdInstance -> RepairCdInstance -> Bool)
-> Eq RepairCdInstance
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RepairCdInstance -> RepairCdInstance -> Bool
== :: RepairCdInstance -> RepairCdInstance -> Bool
$c/= :: RepairCdInstance -> RepairCdInstance -> Bool
/= :: RepairCdInstance -> RepairCdInstance -> Bool
Eq, (forall x. RepairCdInstance -> Rep RepairCdInstance x)
-> (forall x. Rep RepairCdInstance x -> RepairCdInstance)
-> Generic RepairCdInstance
forall x. Rep RepairCdInstance x -> RepairCdInstance
forall x. RepairCdInstance -> Rep RepairCdInstance x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RepairCdInstance -> Rep RepairCdInstance x
from :: forall x. RepairCdInstance -> Rep RepairCdInstance x
$cto :: forall x. Rep RepairCdInstance x -> RepairCdInstance
to :: forall x. Rep RepairCdInstance x -> RepairCdInstance
Generic, ReadPrec [RepairCdInstance]
ReadPrec RepairCdInstance
Int -> ReadS RepairCdInstance
ReadS [RepairCdInstance]
(Int -> ReadS RepairCdInstance)
-> ReadS [RepairCdInstance]
-> ReadPrec RepairCdInstance
-> ReadPrec [RepairCdInstance]
-> Read RepairCdInstance
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RepairCdInstance
readsPrec :: Int -> ReadS RepairCdInstance
$creadList :: ReadS [RepairCdInstance]
readList :: ReadS [RepairCdInstance]
$creadPrec :: ReadPrec RepairCdInstance
readPrec :: ReadPrec RepairCdInstance
$creadListPrec :: ReadPrec [RepairCdInstance]
readListPrec :: ReadPrec [RepairCdInstance]
Read, Int -> RepairCdInstance -> ShowS
[RepairCdInstance] -> ShowS
RepairCdInstance -> String
(Int -> RepairCdInstance -> ShowS)
-> (RepairCdInstance -> String)
-> ([RepairCdInstance] -> ShowS)
-> Show RepairCdInstance
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RepairCdInstance -> ShowS
showsPrec :: Int -> RepairCdInstance -> ShowS
$cshow :: RepairCdInstance -> String
show :: RepairCdInstance -> String
$cshowList :: [RepairCdInstance] -> ShowS
showList :: [RepairCdInstance] -> ShowS
Show)
checkRepairCdInstance :: RepairCdInstance -> Maybe String
checkRepairCdInstance :: RepairCdInstance -> Maybe String
checkRepairCdInstance RepairCdInstance {Bool
RepairCdTaskText
Maybe (Map Language String)
Map Int RelationshipChange
AnyCd
CdDrawSettings
addText :: RepairCdInstance -> Maybe (Map Language String)
changes :: RepairCdInstance -> Map Int RelationshipChange
showSolution :: RepairCdInstance -> Bool
showExtendedFeedback :: RepairCdInstance -> Bool
cdDrawSettings :: RepairCdInstance -> CdDrawSettings
taskText :: RepairCdInstance -> RepairCdTaskText
byName :: RepairCdInstance -> Bool
classDiagram :: RepairCdInstance -> AnyCd
byName :: Bool
cdDrawSettings :: CdDrawSettings
changes :: Map Int RelationshipChange
classDiagram :: AnyCd
showExtendedFeedback :: Bool
showSolution :: Bool
taskText :: RepairCdTaskText
addText :: Maybe (Map Language String)
..}
| Bool -> Bool
not (CdDrawSettings -> Bool
printNames CdDrawSettings
cdDrawSettings) Bool -> Bool -> Bool
&& Bool
byName
= String -> Maybe String
forall a. a -> Maybe a
Just String
"by name is only possible when printing names"
| Bool
showExtendedFeedback Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
showSolution
= String -> Maybe String
forall a. a -> Maybe a
Just [iii|
showExtendedFeedback leaks the correct solution
and thus can only be enabled when showSolution is set to True
|]
| Bool
otherwise
= RepairCdTaskText -> Maybe String
forall element.
(Bounded element, Enum element, Eq element, Show element) =>
[SpecialOutput element] -> Maybe String
checkTaskText RepairCdTaskText
taskText
Maybe String -> Maybe String -> Maybe String
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> CdDrawSettings -> Maybe String
checkCdDrawSettings CdDrawSettings
cdDrawSettings
classAndNonInheritanceNames :: RepairCdInstance -> ([String], [String])
classAndNonInheritanceNames :: RepairCdInstance -> ([String], [String])
classAndNonInheritanceNames RepairCdInstance
inst =
let cd :: AnyCd
cd = RepairCdInstance -> AnyCd
classDiagram RepairCdInstance
inst
allChs :: [RelationshipChange]
allChs = Map Int RelationshipChange -> [RelationshipChange]
forall k a. Map k a -> [a]
M.elems (Map Int RelationshipChange -> [RelationshipChange])
-> Map Int RelationshipChange -> [RelationshipChange]
forall a b. (a -> b) -> a -> b
$ RepairCdInstance -> Map Int RelationshipChange
changes RepairCdInstance
inst
cds :: [AnyCd]
cds = (RelationshipChange -> AnyCd) -> [RelationshipChange] -> [AnyCd]
forall a b. (a -> b) -> [a] -> [b]
map ((AnyCd -> AnyCd) -> (Cd -> AnyCd) -> Either AnyCd Cd -> AnyCd
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either AnyCd -> AnyCd
forall a. a -> a
id Cd -> AnyCd
forall className relationshipName.
ClassDiagram className relationshipName
-> AnyClassDiagram className relationshipName
fromClassDiagram (Either AnyCd Cd -> AnyCd)
-> (RelationshipChange -> Either AnyCd Cd)
-> RelationshipChange
-> AnyCd
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RelationshipChange -> Either AnyCd Cd
forall option forInvalidity forValidity.
InValidOption option forInvalidity forValidity
-> Either forInvalidity forValidity
hint) [RelationshipChange]
allChs
chs :: [Annotation ArticleToUse (Change (AnyRelationship String String))]
chs = (RelationshipChange
-> Annotation
ArticleToUse (Change (AnyRelationship String String)))
-> [RelationshipChange]
-> [Annotation
ArticleToUse (Change (AnyRelationship String String))]
forall a b. (a -> b) -> [a] -> [b]
map RelationshipChange
-> Annotation ArticleToUse (Change (AnyRelationship String String))
forall option forInvalidity forValidity.
InValidOption option forInvalidity forValidity -> option
option [RelationshipChange]
allChs
names :: [String]
names = [String] -> [String]
forall a. Ord a => [a] -> [a]
nubOrd ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ AnyCd -> [String]
forall className relationshipName.
AnyClassDiagram className relationshipName -> [className]
anyClassNames AnyCd
cd
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (AnyCd -> [String]) -> [AnyCd] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap AnyCd -> [String]
forall className relationshipName.
AnyClassDiagram className relationshipName -> [className]
anyClassNames [AnyCd]
cds
nonInheritances :: [String]
nonInheritances = [String] -> [String]
forall a. Ord a => [a] -> [a]
nubOrd ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ AnyCd -> [String]
anyAssociationNames AnyCd
cd
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (Annotation ArticleToUse (Change (AnyRelationship String String))
-> Maybe String)
-> [Annotation
ArticleToUse (Change (AnyRelationship String String))]
-> [String]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Change (AnyRelationship String String)
-> Maybe (AnyRelationship String String)
forall a. Change a -> Maybe a
add (Change (AnyRelationship String String)
-> Maybe (AnyRelationship String String))
-> (Annotation
ArticleToUse (Change (AnyRelationship String String))
-> Change (AnyRelationship String String))
-> Annotation ArticleToUse (Change (AnyRelationship String String))
-> Maybe (AnyRelationship String String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Annotation ArticleToUse (Change (AnyRelationship String String))
-> Change (AnyRelationship String String)
forall annotation annotated.
Annotation annotation annotated -> annotated
annotated (Annotation ArticleToUse (Change (AnyRelationship String String))
-> Maybe (AnyRelationship String String))
-> (AnyRelationship String String -> Maybe String)
-> Annotation ArticleToUse (Change (AnyRelationship String String))
-> Maybe String
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> AnyRelationship String String -> Maybe String
forall className relationshipName.
AnyRelationship className relationshipName
-> Maybe relationshipName
anyRelationshipName) [Annotation ArticleToUse (Change (AnyRelationship String String))]
chs
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (Annotation ArticleToUse (Change (AnyRelationship String String))
-> Maybe String)
-> [Annotation
ArticleToUse (Change (AnyRelationship String String))]
-> [String]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Change (AnyRelationship String String)
-> Maybe (AnyRelationship String String)
forall a. Change a -> Maybe a
remove (Change (AnyRelationship String String)
-> Maybe (AnyRelationship String String))
-> (Annotation
ArticleToUse (Change (AnyRelationship String String))
-> Change (AnyRelationship String String))
-> Annotation ArticleToUse (Change (AnyRelationship String String))
-> Maybe (AnyRelationship String String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Annotation ArticleToUse (Change (AnyRelationship String String))
-> Change (AnyRelationship String String)
forall annotation annotated.
Annotation annotation annotated -> annotated
annotated (Annotation ArticleToUse (Change (AnyRelationship String String))
-> Maybe (AnyRelationship String String))
-> (AnyRelationship String String -> Maybe String)
-> Annotation ArticleToUse (Change (AnyRelationship String String))
-> Maybe String
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> AnyRelationship String String -> Maybe String
forall className relationshipName.
AnyRelationship className relationshipName
-> Maybe relationshipName
anyRelationshipName) [Annotation ArticleToUse (Change (AnyRelationship String String))]
chs
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (AnyCd -> [String]) -> [AnyCd] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap AnyCd -> [String]
anyAssociationNames [AnyCd]
cds
in ([String]
names, [String]
nonInheritances)
instance Randomise RepairCdInstance where
randomise :: forall (m :: * -> *).
(MonadRandom m, MonadThrow m) =>
RepairCdInstance -> m RepairCdInstance
randomise = RepairCdInstance -> m RepairCdInstance
forall (m :: * -> *).
MonadRandom m =>
RepairCdInstance -> m RepairCdInstance
shuffleInstance
instance RandomiseNames RepairCdInstance where
randomiseNames :: forall (m :: * -> *).
(MonadRandom m, MonadThrow m) =>
RepairCdInstance -> m RepairCdInstance
randomiseNames RepairCdInstance
inst = do
let ([String]
names, [String]
nonInheritances) = RepairCdInstance -> ([String], [String])
classAndNonInheritanceNames RepairCdInstance
inst
[String]
names' <- [String] -> m [String]
forall (m :: * -> *) a. MonadRandom m => [a] -> m [a]
shuffleM [String]
names
[String]
nonInheritances' <- [String] -> m [String]
forall (m :: * -> *) a. MonadRandom m => [a] -> m [a]
shuffleM [String]
nonInheritances
RepairCdInstance -> [String] -> [String] -> m RepairCdInstance
forall (m :: * -> *).
MonadThrow m =>
RepairCdInstance -> [String] -> [String] -> m RepairCdInstance
renameInstance RepairCdInstance
inst [String]
names' [String]
nonInheritances'
instance RandomiseLayout RepairCdInstance where
randomiseLayout :: forall (m :: * -> *).
(MonadRandom m, MonadThrow m) =>
RepairCdInstance -> m RepairCdInstance
randomiseLayout RepairCdInstance {Bool
RepairCdTaskText
Maybe (Map Language String)
Map Int RelationshipChange
AnyCd
CdDrawSettings
addText :: RepairCdInstance -> Maybe (Map Language String)
changes :: RepairCdInstance -> Map Int RelationshipChange
showSolution :: RepairCdInstance -> Bool
showExtendedFeedback :: RepairCdInstance -> Bool
cdDrawSettings :: RepairCdInstance -> CdDrawSettings
taskText :: RepairCdInstance -> RepairCdTaskText
byName :: RepairCdInstance -> Bool
classDiagram :: RepairCdInstance -> AnyCd
byName :: Bool
cdDrawSettings :: CdDrawSettings
changes :: Map Int RelationshipChange
classDiagram :: AnyCd
showExtendedFeedback :: Bool
showSolution :: Bool
taskText :: RepairCdTaskText
addText :: Maybe (Map Language String)
..} = do
AnyCd
cd <- AnyCd -> m AnyCd
forall (m :: * -> *). MonadRandom m => AnyCd -> m AnyCd
shuffleAnyClassAndConnectionOrder AnyCd
classDiagram
Map Int RelationshipChange
changes' <- (Annotation ArticleToUse (Change (AnyRelationship String String))
-> m (Annotation
ArticleToUse (Change (AnyRelationship String String))))
-> (AnyCd -> m AnyCd)
-> (Cd -> m Cd)
-> RelationshipChange
-> m RelationshipChange
forall (m :: * -> *) a b c d e f.
Applicative m =>
(a -> m b)
-> (c -> m d)
-> (e -> m f)
-> InValidOption a c e
-> m (InValidOption b d f)
mapInValidOptionM
Annotation ArticleToUse (Change (AnyRelationship String String))
-> m (Annotation
ArticleToUse (Change (AnyRelationship String String)))
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
AnyCd -> m AnyCd
forall (m :: * -> *). MonadRandom m => AnyCd -> m AnyCd
shuffleAnyClassAndConnectionOrder
Cd -> m Cd
forall (m :: * -> *). MonadRandom m => Cd -> m Cd
shuffleClassAndConnectionOrder
(RelationshipChange -> m RelationshipChange)
-> Map Int RelationshipChange -> m (Map Int RelationshipChange)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Map Int a -> m (Map Int b)
`mapM` Map Int RelationshipChange
changes
return RepairCdInstance {
byName :: Bool
byName = Bool
byName,
cdDrawSettings :: CdDrawSettings
cdDrawSettings = CdDrawSettings
cdDrawSettings,
changes :: Map Int RelationshipChange
changes = Map Int RelationshipChange
changes',
classDiagram :: AnyCd
classDiagram = AnyCd
cd,
showExtendedFeedback :: Bool
showExtendedFeedback = Bool
showExtendedFeedback,
showSolution :: Bool
showSolution = Bool
showSolution,
taskText :: RepairCdTaskText
taskText = RepairCdTaskText
taskText,
addText :: Maybe (Map Language String)
addText = Maybe (Map Language String)
addText
}
shuffleInstance :: MonadRandom m => RepairCdInstance -> m RepairCdInstance
shuffleInstance :: forall (m :: * -> *).
MonadRandom m =>
RepairCdInstance -> m RepairCdInstance
shuffleInstance RepairCdInstance {Bool
RepairCdTaskText
Maybe (Map Language String)
Map Int RelationshipChange
AnyCd
CdDrawSettings
addText :: RepairCdInstance -> Maybe (Map Language String)
changes :: RepairCdInstance -> Map Int RelationshipChange
showSolution :: RepairCdInstance -> Bool
showExtendedFeedback :: RepairCdInstance -> Bool
cdDrawSettings :: RepairCdInstance -> CdDrawSettings
taskText :: RepairCdInstance -> RepairCdTaskText
byName :: RepairCdInstance -> Bool
classDiagram :: RepairCdInstance -> AnyCd
byName :: Bool
cdDrawSettings :: CdDrawSettings
changes :: Map Int RelationshipChange
classDiagram :: AnyCd
showExtendedFeedback :: Bool
showSolution :: Bool
taskText :: RepairCdTaskText
addText :: Maybe (Map Language String)
..} = do
Map Int RelationshipChange
chs <- [(Int, RelationshipChange)] -> Map Int RelationshipChange
forall k a. Eq k => [(k, a)] -> Map k a
M.fromAscList ([(Int, RelationshipChange)] -> Map Int RelationshipChange)
-> ([RelationshipChange] -> [(Int, RelationshipChange)])
-> [RelationshipChange]
-> Map Int RelationshipChange
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> [RelationshipChange] -> [(Int, RelationshipChange)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1..] ([RelationshipChange] -> Map Int RelationshipChange)
-> m [RelationshipChange] -> m (Map Int RelationshipChange)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [RelationshipChange] -> m [RelationshipChange]
forall (m :: * -> *) a. MonadRandom m => [a] -> m [a]
shuffleM (Map Int RelationshipChange -> [RelationshipChange]
forall k a. Map k a -> [a]
M.elems Map Int RelationshipChange
changes)
return $ RepairCdInstance {
byName :: Bool
byName = Bool
byName,
cdDrawSettings :: CdDrawSettings
cdDrawSettings = CdDrawSettings
cdDrawSettings,
changes :: Map Int RelationshipChange
changes = Map Int RelationshipChange
chs,
classDiagram :: AnyCd
classDiagram = AnyCd
classDiagram,
showExtendedFeedback :: Bool
showExtendedFeedback = Bool
showExtendedFeedback,
showSolution :: Bool
showSolution = Bool
showSolution,
taskText :: RepairCdTaskText
taskText = RepairCdTaskText
taskText,
addText :: Maybe (Map Language String)
addText = Maybe (Map Language String)
addText
}
renameInstance
:: MonadThrow m
=> RepairCdInstance
-> [String]
-> [String]
-> m RepairCdInstance
renameInstance :: forall (m :: * -> *).
MonadThrow m =>
RepairCdInstance -> [String] -> [String] -> m RepairCdInstance
renameInstance inst :: RepairCdInstance
inst@RepairCdInstance {Bool
RepairCdTaskText
Maybe (Map Language String)
Map Int RelationshipChange
AnyCd
CdDrawSettings
addText :: RepairCdInstance -> Maybe (Map Language String)
changes :: RepairCdInstance -> Map Int RelationshipChange
showSolution :: RepairCdInstance -> Bool
showExtendedFeedback :: RepairCdInstance -> Bool
cdDrawSettings :: RepairCdInstance -> CdDrawSettings
taskText :: RepairCdInstance -> RepairCdTaskText
byName :: RepairCdInstance -> Bool
classDiagram :: RepairCdInstance -> AnyCd
byName :: Bool
cdDrawSettings :: CdDrawSettings
changes :: Map Int RelationshipChange
classDiagram :: AnyCd
showExtendedFeedback :: Bool
showSolution :: Bool
taskText :: RepairCdTaskText
addText :: Maybe (Map Language String)
..} [String]
names' [String]
nonInheritances' = do
let ([String]
names, [String]
nonInheritances) = RepairCdInstance -> ([String], [String])
classAndNonInheritanceNames RepairCdInstance
inst
bmNames :: Bimap String String
bmNames = [(String, String)] -> Bimap String String
forall a b. (Ord a, Ord b) => [(a, b)] -> Bimap a b
BM.fromList ([(String, String)] -> Bimap String String)
-> [(String, String)] -> Bimap String String
forall a b. (a -> b) -> a -> b
$ [String] -> [String] -> [(String, String)]
forall a b. [a] -> [b] -> [(a, b)]
zip [String]
names [String]
names'
bmNonInheritances :: Bimap String String
bmNonInheritances = [(String, String)] -> Bimap String String
forall a b. (Ord a, Ord b) => [(a, b)] -> Bimap a b
BM.fromList ([(String, String)] -> Bimap String String)
-> [(String, String)] -> Bimap String String
forall a b. (a -> b) -> a -> b
$ [String] -> [String] -> [(String, String)]
forall a b. [a] -> [b] -> [(a, b)]
zip [String]
nonInheritances [String]
nonInheritances'
renameCd :: Cd -> m Cd
renameCd = Bimap String String -> Bimap String String -> Cd -> m Cd
forall (f :: * -> * -> *) (m :: * -> *) c c' r r'.
(Bitraversable f, MonadThrow m, Ord c, Ord c', Ord r, Ord r') =>
Bimap c c' -> Bimap r r' -> f c r -> m (f c' r')
renameClassesAndRelationships Bimap String String
bmNames Bimap String String
bmNonInheritances
renameAnyCd :: AnyCd -> m AnyCd
renameAnyCd = Bimap String String -> Bimap String String -> AnyCd -> m AnyCd
forall (f :: * -> * -> *) (m :: * -> *) c c' r r'.
(Bitraversable f, MonadThrow m, Ord c, Ord c', Ord r, Ord r') =>
Bimap c c' -> Bimap r r' -> f c r -> m (f c' r')
renameClassesAndRelationships Bimap String String
bmNames Bimap String String
bmNonInheritances
renameEdge :: Relationship String String -> m (Relationship String String)
renameEdge = Bimap String String
-> Bimap String String
-> Relationship String String
-> m (Relationship String String)
forall (f :: * -> * -> *) (m :: * -> *) c c' r r'.
(Bitraversable f, MonadThrow m, Ord c, Ord c', Ord r, Ord r') =>
Bimap c c' -> Bimap r r' -> f c r -> m (f c' r')
renameClassesAndRelationships Bimap String String
bmNames Bimap String String
bmNonInheritances
renameAnyEdge :: InvalidRelationship String String
-> m (InvalidRelationship String String)
renameAnyEdge = Bimap String String
-> Bimap String String
-> InvalidRelationship String String
-> m (InvalidRelationship String String)
forall (f :: * -> * -> *) (m :: * -> *) c c' r r'.
(Bitraversable f, MonadThrow m, Ord c, Ord c', Ord r, Ord r') =>
Bimap c c' -> Bimap r r' -> f c r -> m (f c' r')
renameClassesAndRelationships Bimap String String
bmNames Bimap String String
bmNonInheritances
renameEdges :: Annotation ArticleToUse (Change (AnyRelationship String String))
-> m (Annotation
ArticleToUse (Change (AnyRelationship String String)))
renameEdges = (Change (AnyRelationship String String)
-> m (Change (AnyRelationship String String)))
-> Annotation ArticleToUse (Change (AnyRelationship String String))
-> m (Annotation
ArticleToUse (Change (AnyRelationship String String)))
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> Annotation ArticleToUse a -> m (Annotation ArticleToUse b)
mapM ((Change (AnyRelationship String String)
-> m (Change (AnyRelationship String String)))
-> Annotation ArticleToUse (Change (AnyRelationship String String))
-> m (Annotation
ArticleToUse (Change (AnyRelationship String String))))
-> (Change (AnyRelationship String String)
-> m (Change (AnyRelationship String String)))
-> Annotation ArticleToUse (Change (AnyRelationship String String))
-> m (Annotation
ArticleToUse (Change (AnyRelationship String String)))
forall a b. (a -> b) -> a -> b
$ (AnyRelationship String String
-> m (AnyRelationship String String))
-> Change (AnyRelationship String String)
-> m (Change (AnyRelationship String String))
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Change a -> m (Change b)
mapM ((AnyRelationship String String
-> m (AnyRelationship String String))
-> Change (AnyRelationship String String)
-> m (Change (AnyRelationship String String)))
-> (AnyRelationship String String
-> m (AnyRelationship String String))
-> Change (AnyRelationship String String)
-> m (Change (AnyRelationship String String))
forall a b. (a -> b) -> a -> b
$ (InvalidRelationship String String
-> m (InvalidRelationship String String))
-> (Relationship String String -> m (Relationship String String))
-> AnyRelationship String String
-> m (AnyRelationship String String)
forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bimapM InvalidRelationship String String
-> m (InvalidRelationship String String)
renameAnyEdge Relationship String String -> m (Relationship String String)
renameEdge
AnyCd
cd <- AnyCd -> m AnyCd
renameAnyCd AnyCd
classDiagram
Map Int RelationshipChange
chs <- (RelationshipChange -> m RelationshipChange)
-> Map Int RelationshipChange -> m (Map Int RelationshipChange)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Map Int a -> m (Map Int b)
mapM
((Annotation ArticleToUse (Change (AnyRelationship String String))
-> m (Annotation
ArticleToUse (Change (AnyRelationship String String))))
-> (AnyCd -> m AnyCd)
-> (Cd -> m Cd)
-> RelationshipChange
-> m RelationshipChange
forall (m :: * -> *) a b c d e f.
Applicative m =>
(a -> m b)
-> (c -> m d)
-> (e -> m f)
-> InValidOption a c e
-> m (InValidOption b d f)
mapInValidOptionM Annotation ArticleToUse (Change (AnyRelationship String String))
-> m (Annotation
ArticleToUse (Change (AnyRelationship String String)))
renameEdges AnyCd -> m AnyCd
renameAnyCd Cd -> m Cd
renameCd)
Map Int RelationshipChange
changes
return $ RepairCdInstance {
byName :: Bool
byName = Bool
byName,
cdDrawSettings :: CdDrawSettings
cdDrawSettings = CdDrawSettings
cdDrawSettings,
changes :: Map Int RelationshipChange
changes = Map Int RelationshipChange
chs,
classDiagram :: AnyCd
classDiagram = AnyCd
cd,
showExtendedFeedback :: Bool
showExtendedFeedback = Bool
showExtendedFeedback,
showSolution :: Bool
showSolution = Bool
showSolution,
taskText :: RepairCdTaskText
taskText = RepairCdTaskText
taskText,
addText :: Maybe (Map Language String)
addText = Maybe (Map Language String)
addText
}
repairCd
:: (MonadAlloy m, MonadCatch m)
=> RepairCdConfig
-> Int
-> Int
-> m RepairCdInstance
repairCd :: forall (m :: * -> *).
(MonadAlloy m, MonadCatch m) =>
RepairCdConfig -> Int -> Int -> m RepairCdInstance
repairCd RepairCdConfig {Bool
[CdMutation]
Maybe Int
Maybe Integer
Maybe (Map Language String)
ArticlePreference
AllowedProperties
ObjectProperties
CdDrawSettings
CdConstraints
ClassConfig
allowedCdMutations :: RepairCdConfig -> [CdMutation]
allowedProperties :: RepairCdConfig -> AllowedProperties
articleToUse :: RepairCdConfig -> ArticlePreference
cdConstraints :: RepairCdConfig -> CdConstraints
classConfig :: RepairCdConfig -> ClassConfig
drawSettings :: RepairCdConfig -> CdDrawSettings
maxInstances :: RepairCdConfig -> Maybe Integer
objectProperties :: RepairCdConfig -> ObjectProperties
printExtendedFeedback :: RepairCdConfig -> Bool
printSolution :: RepairCdConfig -> Bool
timeout :: RepairCdConfig -> Maybe Int
useNames :: RepairCdConfig -> Bool
extraText :: RepairCdConfig -> Maybe (Map Language String)
allowedCdMutations :: [CdMutation]
allowedProperties :: AllowedProperties
articleToUse :: ArticlePreference
cdConstraints :: CdConstraints
classConfig :: ClassConfig
drawSettings :: CdDrawSettings
maxInstances :: Maybe Integer
objectProperties :: ObjectProperties
printExtendedFeedback :: Bool
printSolution :: Bool
timeout :: Maybe Int
useNames :: Bool
extraText :: Maybe (Map Language String)
..} Int
segment Int
seed = (RandT StdGen m RepairCdInstance -> StdGen -> m RepairCdInstance)
-> StdGen -> RandT StdGen m RepairCdInstance -> m RepairCdInstance
forall a b c. (a -> b -> c) -> b -> a -> c
flip RandT StdGen m RepairCdInstance -> StdGen -> m RepairCdInstance
forall (m :: * -> *) g a. Monad m => RandT g m a -> g -> m a
evalRandT StdGen
g (RandT StdGen m RepairCdInstance -> m RepairCdInstance)
-> RandT StdGen m RepairCdInstance -> m RepairCdInstance
forall a b. (a -> b) -> a -> b
$ do
(AnyCd
cd, [CdChangeAndCd]
chs) <- WeakeningKind
-> AllowedProperties
-> ClassConfig
-> CdConstraints
-> [CdMutation]
-> ObjectProperties
-> ArticlePreference
-> Maybe Integer
-> Maybe Int
-> RandT StdGen m (AnyCd, [CdChangeAndCd])
forall (m :: * -> *) g.
(MonadAlloy m, MonadCatch m, RandomGen g) =>
WeakeningKind
-> AllowedProperties
-> ClassConfig
-> CdConstraints
-> [CdMutation]
-> ObjectProperties
-> ArticlePreference
-> Maybe Integer
-> Maybe Int
-> RandT g m (AnyCd, [CdChangeAndCd])
generateSetOfCds
WeakeningKind
IllegalStructuralWeakening
AllowedProperties
allowedProperties
ClassConfig
classConfig
CdConstraints
cdConstraints
[CdMutation]
allowedCdMutations
ObjectProperties
objectProperties
ArticlePreference
articleToUse
Maybe Integer
maxInstances
Maybe Int
timeout
[RelationshipChange]
chs' <- m [RelationshipChange] -> RandT StdGen m [RelationshipChange]
forall (m :: * -> *) a. Monad m => m a -> RandT StdGen m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m [RelationshipChange] -> RandT StdGen m [RelationshipChange])
-> m [RelationshipChange] -> RandT StdGen m [RelationshipChange]
forall a b. (a -> b) -> a -> b
$ (CdChangeAndCd -> m RelationshipChange)
-> [CdChangeAndCd] -> m [RelationshipChange]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CdChangeAndCd -> m RelationshipChange
forall {m :: * -> *} {className} {relationshipName} {annotation}
{c} {e}.
(MonadThrow m, Eq className, Show className, Show relationshipName,
Typeable className, Typeable relationshipName) =>
InValidOption
(AnnotatedChangeAndCd annotation className relationshipName) c e
-> m (InValidOption
(Annotation
annotation (Change (AnyRelationship className relationshipName)))
(AnyClassDiagram className relationshipName)
(ClassDiagram className relationshipName))
cdAsHint [CdChangeAndCd]
chs
RepairCdInstance -> RandT StdGen m RepairCdInstance
forall (m :: * -> *) a.
(MonadRandom m, MonadThrow m, Randomise a, RandomiseLayout a,
RandomiseNames a) =>
a -> m a
shuffleEverything (RepairCdInstance -> RandT StdGen m RepairCdInstance)
-> RepairCdInstance -> RandT StdGen m RepairCdInstance
forall a b. (a -> b) -> a -> b
$ RepairCdInstance {
byName :: Bool
byName = CdDrawSettings -> Bool
printNames CdDrawSettings
drawSettings Bool -> Bool -> Bool
&& Bool
useNames,
cdDrawSettings :: CdDrawSettings
cdDrawSettings = CdDrawSettings
drawSettings,
changes :: Map Int RelationshipChange
changes = [(Int, RelationshipChange)] -> Map Int RelationshipChange
forall k a. Eq k => [(k, a)] -> Map k a
M.fromAscList ([(Int, RelationshipChange)] -> Map Int RelationshipChange)
-> [(Int, RelationshipChange)] -> Map Int RelationshipChange
forall a b. (a -> b) -> a -> b
$ [Int] -> [RelationshipChange] -> [(Int, RelationshipChange)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1..] [RelationshipChange]
chs',
classDiagram :: AnyCd
classDiagram = AnyCd
cd,
showExtendedFeedback :: Bool
showExtendedFeedback = Bool
printExtendedFeedback,
showSolution :: Bool
showSolution = Bool
printSolution,
taskText :: RepairCdTaskText
taskText = RepairCdTaskText
defaultRepairCdTaskText,
addText :: Maybe (Map Language String)
addText = Maybe (Map Language String)
extraText
}
where
g :: StdGen
g = Int -> StdGen
mkStdGen (Int -> StdGen) -> Int -> StdGen
forall a b. (a -> b) -> a -> b
$ (Int
segment Int -> Int -> Int
forall a. Num a => a -> a -> a
+) (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int
4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
seed
cdAsHint :: InValidOption
(AnnotatedChangeAndCd annotation className relationshipName) c e
-> m (InValidOption
(Annotation
annotation (Change (AnyRelationship className relationshipName)))
(AnyClassDiagram className relationshipName)
(ClassDiagram className relationshipName))
cdAsHint InValidOption
(AnnotatedChangeAndCd annotation className relationshipName) c e
x = do
let cd :: p -> f (AnyClassDiagram className relationshipName)
cd p
_ = AnyClassDiagram className relationshipName
-> f (AnyClassDiagram className relationshipName)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AnyClassDiagram className relationshipName
-> f (AnyClassDiagram className relationshipName))
-> AnyClassDiagram className relationshipName
-> f (AnyClassDiagram className relationshipName)
forall a b. (a -> b) -> a -> b
$ AnnotatedChangeAndCd annotation className relationshipName
-> AnyClassDiagram className relationshipName
forall annotation className relationshipName.
AnnotatedChangeAndCd annotation className relationshipName
-> AnyClassDiagram className relationshipName
annotatedChangeClassDiagram (AnnotatedChangeAndCd annotation className relationshipName
-> AnyClassDiagram className relationshipName)
-> AnnotatedChangeAndCd annotation className relationshipName
-> AnyClassDiagram className relationshipName
forall a b. (a -> b) -> a -> b
$ InValidOption
(AnnotatedChangeAndCd annotation className relationshipName) c e
-> AnnotatedChangeAndCd annotation className relationshipName
forall option forInvalidity forValidity.
InValidOption option forInvalidity forValidity -> option
option InValidOption
(AnnotatedChangeAndCd annotation className relationshipName) c e
x
validCd :: p -> m (ClassDiagram className relationshipName)
validCd p
_ = AnyClassDiagram className relationshipName
-> m (ClassDiagram className relationshipName)
forall className (m :: * -> *) relationshipName.
(Eq className, MonadThrow m, Show className, Show relationshipName,
Typeable className, Typeable relationshipName) =>
AnyClassDiagram className relationshipName
-> m (ClassDiagram className relationshipName)
toValidCd (AnyClassDiagram className relationshipName
-> m (ClassDiagram className relationshipName))
-> AnyClassDiagram className relationshipName
-> m (ClassDiagram className relationshipName)
forall a b. (a -> b) -> a -> b
$ AnnotatedChangeAndCd annotation className relationshipName
-> AnyClassDiagram className relationshipName
forall annotation className relationshipName.
AnnotatedChangeAndCd annotation className relationshipName
-> AnyClassDiagram className relationshipName
annotatedChangeClassDiagram (AnnotatedChangeAndCd annotation className relationshipName
-> AnyClassDiagram className relationshipName)
-> AnnotatedChangeAndCd annotation className relationshipName
-> AnyClassDiagram className relationshipName
forall a b. (a -> b) -> a -> b
$ InValidOption
(AnnotatedChangeAndCd annotation className relationshipName) c e
-> AnnotatedChangeAndCd annotation className relationshipName
forall option forInvalidity forValidity.
InValidOption option forInvalidity forValidity -> option
option InValidOption
(AnnotatedChangeAndCd annotation className relationshipName) c e
x
(AnnotatedChangeAndCd annotation className relationshipName
-> m (Annotation
annotation (Change (AnyRelationship className relationshipName))))
-> (c -> m (AnyClassDiagram className relationshipName))
-> (e -> m (ClassDiagram className relationshipName))
-> InValidOption
(AnnotatedChangeAndCd annotation className relationshipName) c e
-> m (InValidOption
(Annotation
annotation (Change (AnyRelationship className relationshipName)))
(AnyClassDiagram className relationshipName)
(ClassDiagram className relationshipName))
forall (m :: * -> *) a b c d e f.
Applicative m =>
(a -> m b)
-> (c -> m d)
-> (e -> m f)
-> InValidOption a c e
-> m (InValidOption b d f)
mapInValidOptionM (Annotation
annotation (Change (AnyRelationship className relationshipName))
-> m (Annotation
annotation (Change (AnyRelationship className relationshipName)))
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Annotation
annotation (Change (AnyRelationship className relationshipName))
-> m (Annotation
annotation (Change (AnyRelationship className relationshipName))))
-> (AnnotatedChangeAndCd annotation className relationshipName
-> Annotation
annotation (Change (AnyRelationship className relationshipName)))
-> AnnotatedChangeAndCd annotation className relationshipName
-> m (Annotation
annotation (Change (AnyRelationship className relationshipName)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnnotatedChangeAndCd annotation className relationshipName
-> Annotation
annotation (Change (AnyRelationship className relationshipName))
forall annotation className relationshipName.
AnnotatedChangeAndCd annotation className relationshipName
-> Annotation
annotation (Change (AnyRelationship className relationshipName))
annotatedRelationshipChange) c -> m (AnyClassDiagram className relationshipName)
forall {f :: * -> *} {p}.
Applicative f =>
p -> f (AnyClassDiagram className relationshipName)
cd e -> m (ClassDiagram className relationshipName)
forall {m :: * -> *} {p}.
MonadThrow m =>
p -> m (ClassDiagram className relationshipName)
validCd InValidOption
(AnnotatedChangeAndCd annotation className relationshipName) c e
x
defaultRepairCdInstance :: RepairCdInstance
defaultRepairCdInstance :: RepairCdInstance
defaultRepairCdInstance = RepairCdInstance {
byName :: Bool
byName = Bool
True,
cdDrawSettings :: CdDrawSettings
cdDrawSettings = CdDrawSettings {
omittedDefaults :: OmittedDefaultMultiplicities
omittedDefaults = OmittedDefaultMultiplicities {
aggregationWholeOmittedDefaultMultiplicity :: Maybe (Int, Maybe Int)
aggregationWholeOmittedDefaultMultiplicity = (Int, Maybe Int) -> Maybe (Int, Maybe Int)
forall a. a -> Maybe a
Just (Int
0, Maybe Int
forall a. Maybe a
Nothing),
associationOmittedDefaultMultiplicity :: Maybe (Int, Maybe Int)
associationOmittedDefaultMultiplicity = (Int, Maybe Int) -> Maybe (Int, Maybe Int)
forall a. a -> Maybe a
Just (Int
0, Maybe Int
forall a. Maybe a
Nothing),
compositionWholeOmittedDefaultMultiplicity :: Maybe (Int, Maybe Int)
compositionWholeOmittedDefaultMultiplicity = (Int, Maybe Int) -> Maybe (Int, Maybe Int)
forall a. a -> Maybe a
Just (Int
1, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1)
},
printNames :: Bool
printNames = Bool
True,
printNavigations :: Bool
printNavigations = Bool
True
},
changes :: Map Int RelationshipChange
changes = [(Int, RelationshipChange)] -> Map Int RelationshipChange
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [
(Int
1, InValidOption {
hint :: Either AnyCd Cd
hint = AnyCd -> Either AnyCd Cd
forall a b. a -> Either a b
Left AnyClassDiagram {
anyClassNames :: [String]
anyClassNames = [String
"D", String
"C", String
"A", String
"B"],
anyRelationships :: [AnyRelationship String String]
anyRelationships = [
Relationship String String -> AnyRelationship String String
forall a b. b -> Either a b
Right Composition {
compositionName :: String
compositionName = String
"z",
compositionPart :: LimitedLinking String
compositionPart =
LimitedLinking {linking :: String
linking = String
"A", limits :: (Int, Maybe Int)
limits = (Int
0, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
2)},
compositionWhole :: LimitedLinking String
compositionWhole =
LimitedLinking {linking :: String
linking = String
"C", limits :: (Int, Maybe Int)
limits = (Int
1, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1)}
},
Relationship String String -> AnyRelationship String String
forall a b. b -> Either a b
Right Composition {
compositionName :: String
compositionName = String
"v",
compositionPart :: LimitedLinking String
compositionPart =
LimitedLinking {linking :: String
linking = String
"D", limits :: (Int, Maybe Int)
limits = (Int
1, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
2)},
compositionWhole :: LimitedLinking String
compositionWhole =
LimitedLinking {linking :: String
linking = String
"A", limits :: (Int, Maybe Int)
limits = (Int
0, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1)}
},
Relationship String String -> AnyRelationship String String
forall a b. b -> Either a b
Right Composition {
compositionName :: String
compositionName = String
"w",
compositionPart :: LimitedLinking String
compositionPart =
LimitedLinking {linking :: String
linking = String
"C", limits :: (Int, Maybe Int)
limits = (Int
0, Maybe Int
forall a. Maybe a
Nothing)},
compositionWhole :: LimitedLinking String
compositionWhole =
LimitedLinking {linking :: String
linking = String
"D", limits :: (Int, Maybe Int)
limits = (Int
1, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1)}
},
Relationship String String -> AnyRelationship String String
forall a b. b -> Either a b
Right Association {
associationName :: String
associationName = String
"x",
associationFrom :: LimitedLinking String
associationFrom =
LimitedLinking {linking :: String
linking = String
"B", limits :: (Int, Maybe Int)
limits = (Int
2, Maybe Int
forall a. Maybe a
Nothing)},
associationTo :: LimitedLinking String
associationTo =
LimitedLinking {linking :: String
linking = String
"A", limits :: (Int, Maybe Int)
limits = (Int
2, Maybe Int
forall a. Maybe a
Nothing)}
}
]
},
option :: Annotation ArticleToUse (Change (AnyRelationship String String))
option = Annotation {
annotated :: Change (AnyRelationship String String)
annotated = Change {
add :: Maybe (AnyRelationship String String)
add = AnyRelationship String String
-> Maybe (AnyRelationship String String)
forall a. a -> Maybe a
Just (AnyRelationship String String
-> Maybe (AnyRelationship String String))
-> AnyRelationship String String
-> Maybe (AnyRelationship String String)
forall a b. (a -> b) -> a -> b
$ Relationship String String -> AnyRelationship String String
forall a b. b -> Either a b
Right Association {
associationName :: String
associationName = String
"x",
associationFrom :: LimitedLinking String
associationFrom =
LimitedLinking {linking :: String
linking = String
"B", limits :: (Int, Maybe Int)
limits = (Int
2, Maybe Int
forall a. Maybe a
Nothing)},
associationTo :: LimitedLinking String
associationTo =
LimitedLinking {linking :: String
linking = String
"A", limits :: (Int, Maybe Int)
limits = (Int
2, Maybe Int
forall a. Maybe a
Nothing)}
},
remove :: Maybe (AnyRelationship String String)
remove = Maybe (AnyRelationship String String)
forall a. Maybe a
Nothing
},
annotation :: ArticleToUse
annotation = ArticleToUse
DefiniteArticle
}
}),
(Int
2, InValidOption {
hint :: Either AnyCd Cd
hint = AnyCd -> Either AnyCd Cd
forall a b. a -> Either a b
Left AnyClassDiagram {
anyClassNames :: [String]
anyClassNames = [String
"C", String
"D", String
"B", String
"A"],
anyRelationships :: [AnyRelationship String String]
anyRelationships = [
Relationship String String -> AnyRelationship String String
forall a b. b -> Either a b
Right Association {
associationName :: String
associationName = String
"y",
associationFrom :: LimitedLinking String
associationFrom =
LimitedLinking {linking :: String
linking = String
"A", limits :: (Int, Maybe Int)
limits = (Int
2, Maybe Int
forall a. Maybe a
Nothing)},
associationTo :: LimitedLinking String
associationTo =
LimitedLinking {linking :: String
linking = String
"B", limits :: (Int, Maybe Int)
limits = (Int
2, Maybe Int
forall a. Maybe a
Nothing)}
},
Relationship String String -> AnyRelationship String String
forall a b. b -> Either a b
Right Composition {
compositionName :: String
compositionName = String
"z",
compositionPart :: LimitedLinking String
compositionPart =
LimitedLinking {linking :: String
linking = String
"A", limits :: (Int, Maybe Int)
limits = (Int
0, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
2)},
compositionWhole :: LimitedLinking String
compositionWhole =
LimitedLinking {linking :: String
linking = String
"C", limits :: (Int, Maybe Int)
limits = (Int
1, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1)}
},
Relationship String String -> AnyRelationship String String
forall a b. b -> Either a b
Right Composition {
compositionName :: String
compositionName = String
"w",
compositionPart :: LimitedLinking String
compositionPart =
LimitedLinking {linking :: String
linking = String
"C", limits :: (Int, Maybe Int)
limits = (Int
0, Maybe Int
forall a. Maybe a
Nothing)},
compositionWhole :: LimitedLinking String
compositionWhole =
LimitedLinking {linking :: String
linking = String
"D", limits :: (Int, Maybe Int)
limits = (Int
1, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1)}
},
Relationship String String -> AnyRelationship String String
forall a b. b -> Either a b
Right Composition {
compositionName :: String
compositionName = String
"v",
compositionPart :: LimitedLinking String
compositionPart =
LimitedLinking {linking :: String
linking = String
"D", limits :: (Int, Maybe Int)
limits = (Int
1, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
2)},
compositionWhole :: LimitedLinking String
compositionWhole =
LimitedLinking {linking :: String
linking = String
"A", limits :: (Int, Maybe Int)
limits = (Int
0, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1)}
}
]
},
option :: Annotation ArticleToUse (Change (AnyRelationship String String))
option = Annotation {
annotated :: Change (AnyRelationship String String)
annotated = Change {
add :: Maybe (AnyRelationship String String)
add = AnyRelationship String String
-> Maybe (AnyRelationship String String)
forall a. a -> Maybe a
Just (AnyRelationship String String
-> Maybe (AnyRelationship String String))
-> AnyRelationship String String
-> Maybe (AnyRelationship String String)
forall a b. (a -> b) -> a -> b
$ Relationship String String -> AnyRelationship String String
forall a b. b -> Either a b
Right Association {
associationName :: String
associationName = String
"y",
associationFrom :: LimitedLinking String
associationFrom =
LimitedLinking {linking :: String
linking = String
"A", limits :: (Int, Maybe Int)
limits = (Int
2, Maybe Int
forall a. Maybe a
Nothing)},
associationTo :: LimitedLinking String
associationTo =
LimitedLinking {linking :: String
linking = String
"B", limits :: (Int, Maybe Int)
limits = (Int
2, Maybe Int
forall a. Maybe a
Nothing)}
},
remove :: Maybe (AnyRelationship String String)
remove = Maybe (AnyRelationship String String)
forall a. Maybe a
Nothing
},
annotation :: ArticleToUse
annotation = ArticleToUse
DefiniteArticle
}
}),
(Int
3, InValidOption {
hint :: Either AnyCd Cd
hint = Cd -> Either AnyCd Cd
forall a b. b -> Either a b
Right ClassDiagram {
classNames :: [String]
classNames = [String
"D", String
"A", String
"B", String
"C"],
relationships :: [Relationship String String]
relationships = [
Composition {
compositionName :: String
compositionName = String
"z",
compositionPart :: LimitedLinking String
compositionPart =
LimitedLinking {linking :: String
linking = String
"A", limits :: (Int, Maybe Int)
limits = (Int
0, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
2)},
compositionWhole :: LimitedLinking String
compositionWhole =
LimitedLinking {linking :: String
linking = String
"C", limits :: (Int, Maybe Int)
limits = (Int
1, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1)}
},
Composition {
compositionName :: String
compositionName = String
"w",
compositionPart :: LimitedLinking String
compositionPart =
LimitedLinking {linking :: String
linking = String
"C", limits :: (Int, Maybe Int)
limits = (Int
0, Maybe Int
forall a. Maybe a
Nothing)},
compositionWhole :: LimitedLinking String
compositionWhole =
LimitedLinking {linking :: String
linking = String
"D", limits :: (Int, Maybe Int)
limits = (Int
1, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1)}
}
]
},
option :: Annotation ArticleToUse (Change (AnyRelationship String String))
option = Annotation {
annotated :: Change (AnyRelationship String String)
annotated = Change {
add :: Maybe (AnyRelationship String String)
add = Maybe (AnyRelationship String String)
forall a. Maybe a
Nothing,
remove :: Maybe (AnyRelationship String String)
remove = AnyRelationship String String
-> Maybe (AnyRelationship String String)
forall a. a -> Maybe a
Just (AnyRelationship String String
-> Maybe (AnyRelationship String String))
-> AnyRelationship String String
-> Maybe (AnyRelationship String String)
forall a b. (a -> b) -> a -> b
$ Relationship String String -> AnyRelationship String String
forall a b. b -> Either a b
Right Composition {
compositionName :: String
compositionName = String
"v",
compositionPart :: LimitedLinking String
compositionPart =
LimitedLinking {linking :: String
linking = String
"D", limits :: (Int, Maybe Int)
limits = (Int
1, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
2)},
compositionWhole :: LimitedLinking String
compositionWhole =
LimitedLinking {linking :: String
linking = String
"A", limits :: (Int, Maybe Int)
limits = (Int
0, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1)}
}
},
annotation :: ArticleToUse
annotation = ArticleToUse
DefiniteArticle
}
}),
(Int
4, InValidOption {
hint :: Either AnyCd Cd
hint = Cd -> Either AnyCd Cd
forall a b. b -> Either a b
Right ClassDiagram {
classNames :: [String]
classNames = [String
"C", String
"A", String
"D", String
"B"],
relationships :: [Relationship String String]
relationships = [
Composition {
compositionName :: String
compositionName = String
"v",
compositionPart :: LimitedLinking String
compositionPart =
LimitedLinking {linking :: String
linking = String
"D", limits :: (Int, Maybe Int)
limits = (Int
1, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
2)},
compositionWhole :: LimitedLinking String
compositionWhole =
LimitedLinking {linking :: String
linking = String
"A", limits :: (Int, Maybe Int)
limits = (Int
0, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1)}
},
Composition {
compositionName :: String
compositionName = String
"z",
compositionPart :: LimitedLinking String
compositionPart =
LimitedLinking {linking :: String
linking = String
"A", limits :: (Int, Maybe Int)
limits = (Int
0, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
2)},
compositionWhole :: LimitedLinking String
compositionWhole =
LimitedLinking {linking :: String
linking = String
"C", limits :: (Int, Maybe Int)
limits = (Int
1, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1)}
}
]
},
option :: Annotation ArticleToUse (Change (AnyRelationship String String))
option = Annotation {
annotated :: Change (AnyRelationship String String)
annotated = Change {
add :: Maybe (AnyRelationship String String)
add = Maybe (AnyRelationship String String)
forall a. Maybe a
Nothing,
remove :: Maybe (AnyRelationship String String)
remove = AnyRelationship String String
-> Maybe (AnyRelationship String String)
forall a. a -> Maybe a
Just (AnyRelationship String String
-> Maybe (AnyRelationship String String))
-> AnyRelationship String String
-> Maybe (AnyRelationship String String)
forall a b. (a -> b) -> a -> b
$ Relationship String String -> AnyRelationship String String
forall a b. b -> Either a b
Right Composition {
compositionName :: String
compositionName = String
"w",
compositionPart :: LimitedLinking String
compositionPart =
LimitedLinking {linking :: String
linking = String
"C", limits :: (Int, Maybe Int)
limits = (Int
0, Maybe Int
forall a. Maybe a
Nothing)},
compositionWhole :: LimitedLinking String
compositionWhole =
LimitedLinking {linking :: String
linking = String
"D", limits :: (Int, Maybe Int)
limits = (Int
1, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1)}
}
},
annotation :: ArticleToUse
annotation = ArticleToUse
DefiniteArticle
}
})
],
classDiagram :: AnyCd
classDiagram = AnyClassDiagram {
anyClassNames :: [String]
anyClassNames = [String
"C", String
"D", String
"B", String
"A"],
anyRelationships :: [AnyRelationship String String]
anyRelationships = [
Relationship String String -> AnyRelationship String String
forall a b. b -> Either a b
Right Composition {
compositionName :: String
compositionName = String
"w",
compositionPart :: LimitedLinking String
compositionPart =
LimitedLinking {linking :: String
linking = String
"C", limits :: (Int, Maybe Int)
limits = (Int
0, Maybe Int
forall a. Maybe a
Nothing)},
compositionWhole :: LimitedLinking String
compositionWhole =
LimitedLinking {linking :: String
linking = String
"D", limits :: (Int, Maybe Int)
limits = (Int
1, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1)}
},
Relationship String String -> AnyRelationship String String
forall a b. b -> Either a b
Right Composition {
compositionName :: String
compositionName = String
"v",
compositionPart :: LimitedLinking String
compositionPart =
LimitedLinking {linking :: String
linking = String
"D", limits :: (Int, Maybe Int)
limits = (Int
1, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
2)},
compositionWhole :: LimitedLinking String
compositionWhole =
LimitedLinking {linking :: String
linking = String
"A", limits :: (Int, Maybe Int)
limits = (Int
0, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1)}
},
Relationship String String -> AnyRelationship String String
forall a b. b -> Either a b
Right Composition {
compositionName :: String
compositionName = String
"z",
compositionPart :: LimitedLinking String
compositionPart =
LimitedLinking {linking :: String
linking = String
"A", limits :: (Int, Maybe Int)
limits = (Int
0, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
2)},
compositionWhole :: LimitedLinking String
compositionWhole =
LimitedLinking {linking :: String
linking = String
"C", limits :: (Int, Maybe Int)
limits = (Int
1, Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1)}
}
]
},
showExtendedFeedback :: Bool
showExtendedFeedback = Bool
True,
showSolution :: Bool
showSolution = Bool
True,
taskText :: RepairCdTaskText
taskText = RepairCdTaskText
defaultRepairCdTaskText,
addText :: Maybe (Map Language String)
addText = Maybe (Map Language String)
forall a. Maybe a
Nothing
}
type StructuralWeakeningSet = WeakeningSet StructuralWeakening
data WeakeningSet a = WeakeningSet {
forall a. WeakeningSet a -> a
initialWeakening :: !a,
forall a. WeakeningSet a -> [a]
otherWeakenings :: ![a]
} deriving (WeakeningSet a -> WeakeningSet a -> Bool
(WeakeningSet a -> WeakeningSet a -> Bool)
-> (WeakeningSet a -> WeakeningSet a -> Bool)
-> Eq (WeakeningSet a)
forall a. Eq a => WeakeningSet a -> WeakeningSet a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => WeakeningSet a -> WeakeningSet a -> Bool
== :: WeakeningSet a -> WeakeningSet a -> Bool
$c/= :: forall a. Eq a => WeakeningSet a -> WeakeningSet a -> Bool
/= :: WeakeningSet a -> WeakeningSet a -> Bool
Eq, (forall a b. (a -> b) -> WeakeningSet a -> WeakeningSet b)
-> (forall a b. a -> WeakeningSet b -> WeakeningSet a)
-> Functor WeakeningSet
forall a b. a -> WeakeningSet b -> WeakeningSet a
forall a b. (a -> b) -> WeakeningSet a -> WeakeningSet b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> WeakeningSet a -> WeakeningSet b
fmap :: forall a b. (a -> b) -> WeakeningSet a -> WeakeningSet b
$c<$ :: forall a b. a -> WeakeningSet b -> WeakeningSet a
<$ :: forall a b. a -> WeakeningSet b -> WeakeningSet a
Functor, Eq (WeakeningSet a)
Eq (WeakeningSet a)
-> (WeakeningSet a -> WeakeningSet a -> Ordering)
-> (WeakeningSet a -> WeakeningSet a -> Bool)
-> (WeakeningSet a -> WeakeningSet a -> Bool)
-> (WeakeningSet a -> WeakeningSet a -> Bool)
-> (WeakeningSet a -> WeakeningSet a -> Bool)
-> (WeakeningSet a -> WeakeningSet a -> WeakeningSet a)
-> (WeakeningSet a -> WeakeningSet a -> WeakeningSet a)
-> Ord (WeakeningSet a)
WeakeningSet a -> WeakeningSet a -> Bool
WeakeningSet a -> WeakeningSet a -> Ordering
WeakeningSet a -> WeakeningSet a -> WeakeningSet a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {a}. Ord a => Eq (WeakeningSet a)
forall a. Ord a => WeakeningSet a -> WeakeningSet a -> Bool
forall a. Ord a => WeakeningSet a -> WeakeningSet a -> Ordering
forall a.
Ord a =>
WeakeningSet a -> WeakeningSet a -> WeakeningSet a
$ccompare :: forall a. Ord a => WeakeningSet a -> WeakeningSet a -> Ordering
compare :: WeakeningSet a -> WeakeningSet a -> Ordering
$c< :: forall a. Ord a => WeakeningSet a -> WeakeningSet a -> Bool
< :: WeakeningSet a -> WeakeningSet a -> Bool
$c<= :: forall a. Ord a => WeakeningSet a -> WeakeningSet a -> Bool
<= :: WeakeningSet a -> WeakeningSet a -> Bool
$c> :: forall a. Ord a => WeakeningSet a -> WeakeningSet a -> Bool
> :: WeakeningSet a -> WeakeningSet a -> Bool
$c>= :: forall a. Ord a => WeakeningSet a -> WeakeningSet a -> Bool
>= :: WeakeningSet a -> WeakeningSet a -> Bool
$cmax :: forall a.
Ord a =>
WeakeningSet a -> WeakeningSet a -> WeakeningSet a
max :: WeakeningSet a -> WeakeningSet a -> WeakeningSet a
$cmin :: forall a.
Ord a =>
WeakeningSet a -> WeakeningSet a -> WeakeningSet a
min :: WeakeningSet a -> WeakeningSet a -> WeakeningSet a
Ord)
possibleWeakenings
:: WeakeningKind
-> AllowedProperties
-> [StructuralWeakeningSet]
possibleWeakenings :: WeakeningKind -> AllowedProperties -> [StructuralWeakeningSet]
possibleWeakenings WeakeningKind
basis AllowedProperties
allowed = (StructuralWeakeningSet -> WeakeningSet [Weakening])
-> [StructuralWeakeningSet] -> [StructuralWeakeningSet]
forall b a. Ord b => (a -> b) -> [a] -> [a]
nubOrdOn
((StructuralWeakening -> [Weakening])
-> StructuralWeakeningSet -> WeakeningSet [Weakening]
forall a b. (a -> b) -> WeakeningSet a -> WeakeningSet b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap StructuralWeakening -> [Weakening]
weakeningName)
[ WeakeningSet {
initialWeakening :: StructuralWeakening
initialWeakening = StructuralWeakening
initial,
otherWeakenings :: [StructuralWeakening]
otherWeakenings =
(StructuralWeakening -> [Weakening])
-> [StructuralWeakening] -> [StructuralWeakening]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn StructuralWeakening -> [Weakening]
weakeningName [StructuralWeakening
other StructuralWeakening -> StructuralWeakening -> StructuralWeakening
.&. StructuralWeakening
initial, StructuralWeakening
noStructuralWeakening, StructuralWeakening
w1, StructuralWeakening
w2]
}
| StructuralWeakening
iw <- AllowedProperties -> [StructuralWeakening]
illegalStructuralWeakenings AllowedProperties
allowed
, StructuralWeakening
l1 <- AllowedProperties -> [StructuralWeakening]
legalStructuralWeakenings AllowedProperties
allowed
, (StructuralWeakening
initial, StructuralWeakening
other) <- case WeakeningKind
basis of
WeakeningKind
AnyStructuralWeakening -> [(StructuralWeakening
l1, StructuralWeakening
iw), (StructuralWeakening
iw, StructuralWeakening
l1)]
WeakeningKind
IllegalStructuralWeakening -> [(StructuralWeakening
iw, StructuralWeakening
l1) ]
WeakeningKind
LegalStructuralWeakening -> [(StructuralWeakening
l1, StructuralWeakening
iw)]
, StructuralWeakening
l2 <- AllowedProperties -> [StructuralWeakening]
legalStructuralWeakenings AllowedProperties
allowed
, StructuralWeakening
w <- AllowedProperties -> [StructuralWeakening]
allStructuralWeakenings AllowedProperties
allowed
, let weakenings :: [StructuralWeakening]
weakenings = [StructuralWeakening
w, StructuralWeakening
noStructuralWeakening, StructuralWeakening
iw, StructuralWeakening
l2, StructuralWeakening
l2]
, StructuralWeakening
w1 <- [StructuralWeakening]
weakenings
, StructuralWeakening
w2 <- (StructuralWeakening -> StructuralWeakening -> Bool)
-> StructuralWeakening
-> [StructuralWeakening]
-> [StructuralWeakening]
forall a. (a -> a -> Bool) -> a -> [a] -> [a]
deleteBy ([Weakening] -> [Weakening] -> Bool
forall a. Eq a => a -> a -> Bool
(==) ([Weakening] -> [Weakening] -> Bool)
-> (StructuralWeakening -> [Weakening])
-> StructuralWeakening
-> StructuralWeakening
-> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` StructuralWeakening -> [Weakening]
weakeningName) StructuralWeakening
w1 [StructuralWeakening]
weakenings
]
diversify :: [StructuralWeakeningSet] -> [StructuralWeakeningSet]
diversify :: [StructuralWeakeningSet] -> [StructuralWeakeningSet]
diversify = (Int -> StructuralWeakeningSet -> StructuralWeakeningSet)
-> [Int] -> [StructuralWeakeningSet] -> [StructuralWeakeningSet]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int -> StructuralWeakeningSet -> StructuralWeakeningSet
forall {a}. Int -> WeakeningSet a -> WeakeningSet a
permutate [Int
0..]
where
permutate :: Int -> WeakeningSet a -> WeakeningSet a
permutate Int
g WeakeningSet a
c = WeakeningSet a
c {
otherWeakenings :: [a]
otherWeakenings = [a] -> Int -> StdGen -> [a]
forall gen a. RandomGen gen => [a] -> Int -> gen -> [a]
shuffle' (WeakeningSet a -> [a]
forall a. WeakeningSet a -> [a]
otherWeakenings WeakeningSet a
c) Int
4 (StdGen -> [a]) -> StdGen -> [a]
forall a b. (a -> b) -> a -> b
$ Int -> StdGen
mkStdGen Int
g
}
data WeakeningKind
= AnyStructuralWeakening
| IllegalStructuralWeakening
| LegalStructuralWeakening
deriving ((forall x. WeakeningKind -> Rep WeakeningKind x)
-> (forall x. Rep WeakeningKind x -> WeakeningKind)
-> Generic WeakeningKind
forall x. Rep WeakeningKind x -> WeakeningKind
forall x. WeakeningKind -> Rep WeakeningKind x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. WeakeningKind -> Rep WeakeningKind x
from :: forall x. WeakeningKind -> Rep WeakeningKind x
$cto :: forall x. Rep WeakeningKind x -> WeakeningKind
to :: forall x. Rep WeakeningKind x -> WeakeningKind
Generic, ReadPrec [WeakeningKind]
ReadPrec WeakeningKind
Int -> ReadS WeakeningKind
ReadS [WeakeningKind]
(Int -> ReadS WeakeningKind)
-> ReadS [WeakeningKind]
-> ReadPrec WeakeningKind
-> ReadPrec [WeakeningKind]
-> Read WeakeningKind
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS WeakeningKind
readsPrec :: Int -> ReadS WeakeningKind
$creadList :: ReadS [WeakeningKind]
readList :: ReadS [WeakeningKind]
$creadPrec :: ReadPrec WeakeningKind
readPrec :: ReadPrec WeakeningKind
$creadListPrec :: ReadPrec [WeakeningKind]
readListPrec :: ReadPrec [WeakeningKind]
Read, Int -> WeakeningKind -> ShowS
[WeakeningKind] -> ShowS
WeakeningKind -> String
(Int -> WeakeningKind -> ShowS)
-> (WeakeningKind -> String)
-> ([WeakeningKind] -> ShowS)
-> Show WeakeningKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WeakeningKind -> ShowS
showsPrec :: Int -> WeakeningKind -> ShowS
$cshow :: WeakeningKind -> String
show :: WeakeningKind -> String
$cshowList :: [WeakeningKind] -> ShowS
showList :: [WeakeningKind] -> ShowS
Show)
generateSetOfCds
:: (MonadAlloy m, MonadCatch m, RandomGen g)
=> WeakeningKind
-> AllowedProperties
-> ClassConfig
-> CdConstraints
-> [CdMutation]
-> ObjectProperties
-> ArticlePreference
-> Maybe Integer
-> Maybe Int
-> RandT g m (AnyCd, [CdChangeAndCd])
generateSetOfCds :: forall (m :: * -> *) g.
(MonadAlloy m, MonadCatch m, RandomGen g) =>
WeakeningKind
-> AllowedProperties
-> ClassConfig
-> CdConstraints
-> [CdMutation]
-> ObjectProperties
-> ArticlePreference
-> Maybe Integer
-> Maybe Int
-> RandT g m (AnyCd, [CdChangeAndCd])
generateSetOfCds
WeakeningKind
basisCd
AllowedProperties
cdProperties
ClassConfig
config
CdConstraints
cdConstraints
[CdMutation]
cdMutations
ObjectProperties
objectProperties
ArticlePreference
preference
Maybe Integer
maxInstances
Maybe Int
to
= do
[StructuralWeakeningSet]
weakeningSets <- [StructuralWeakeningSet] -> RandT g m [StructuralWeakeningSet]
forall (m :: * -> *) a. MonadRandom m => [a] -> m [a]
shuffleM ([StructuralWeakeningSet] -> RandT g m [StructuralWeakeningSet])
-> [StructuralWeakeningSet] -> RandT g m [StructuralWeakeningSet]
forall a b. (a -> b) -> a -> b
$ [StructuralWeakeningSet] -> [StructuralWeakeningSet]
diversify
([StructuralWeakeningSet] -> [StructuralWeakeningSet])
-> [StructuralWeakeningSet] -> [StructuralWeakeningSet]
forall a b. (a -> b) -> a -> b
$ WeakeningKind -> AllowedProperties -> [StructuralWeakeningSet]
possibleWeakenings WeakeningKind
basisCd AllowedProperties
cdProperties
[StructuralWeakeningSet] -> RandT g m (AnyCd, [CdChangeAndCd])
forall {t :: (* -> *) -> * -> *} {m :: * -> *}.
(MonadTrans t, MonadAlloy (t m), MonadRandom (t m), MonadThrow m,
MonadCatch (t m)) =>
[StructuralWeakeningSet] -> t m (AnyCd, [CdChangeAndCd])
tryNextWeakeningSet [StructuralWeakeningSet]
weakeningSets
where
tryNextWeakeningSet :: [StructuralWeakeningSet] -> t m (AnyCd, [CdChangeAndCd])
tryNextWeakeningSet [] = m (AnyCd, [CdChangeAndCd]) -> t m (AnyCd, [CdChangeAndCd])
forall (m :: * -> *) a. Monad m => m a -> t m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (AnyCd, [CdChangeAndCd]) -> t m (AnyCd, [CdChangeAndCd]))
-> m (AnyCd, [CdChangeAndCd]) -> t m (AnyCd, [CdChangeAndCd])
forall a b. (a -> b) -> a -> b
$ TaskGenerationException -> m (AnyCd, [CdChangeAndCd])
forall e a. Exception e => e -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM TaskGenerationException
NoInstanceAvailable
tryNextWeakeningSet (WeakeningSet {[StructuralWeakening]
StructuralWeakening
initialWeakening :: forall a. WeakeningSet a -> a
otherWeakenings :: forall a. WeakeningSet a -> [a]
initialWeakening :: StructuralWeakening
otherWeakenings :: [StructuralWeakening]
..} : [StructuralWeakeningSet]
weakeningSets) = do
let alloyCode :: String
alloyCode = ClassConfig
-> CdConstraints
-> [CdMutation]
-> RelationshipProperties
-> Maybe ClassConfig
-> [RelationshipProperties]
-> String
Changes.transformChanges
ClassConfig
config
CdConstraints
cdConstraints
[CdMutation]
cdMutations
(StructuralWeakening -> RelationshipProperties
toProperty StructuralWeakening
initialWeakening)
(ClassConfig -> Maybe ClassConfig
forall a. a -> Maybe a
Just ClassConfig
config)
([RelationshipProperties] -> String)
-> [RelationshipProperties] -> String
forall a b. (a -> b) -> a -> b
$ (StructuralWeakening -> RelationshipProperties)
-> [StructuralWeakening] -> [RelationshipProperties]
forall a b. (a -> b) -> [a] -> [b]
map StructuralWeakening -> RelationshipProperties
toProperty [StructuralWeakening]
otherWeakenings
[AlloyInstance]
instances <- Maybe Integer -> Maybe Int -> String -> t m [AlloyInstance]
forall (m :: * -> *).
MonadAlloy m =>
Maybe Integer -> Maybe Int -> String -> m [AlloyInstance]
getInstances Maybe Integer
maxInstances Maybe Int
to String
alloyCode
[AlloyInstance]
randomInstances <- [AlloyInstance] -> t m [AlloyInstance]
forall (m :: * -> *) a. MonadRandom m => [a] -> m [a]
shuffleM [AlloyInstance]
instances
[StructuralWeakeningSet]
-> [StructuralWeakening]
-> [AlloyInstance]
-> t m (AnyCd, [CdChangeAndCd])
getInstanceWithODs [StructuralWeakeningSet]
weakeningSets [StructuralWeakening]
otherWeakenings [AlloyInstance]
randomInstances
article :: ArticleToUse
article = ArticlePreference -> ArticleToUse
toArticleToUse ArticlePreference
preference
getInstanceWithODs :: [StructuralWeakeningSet]
-> [StructuralWeakening]
-> [AlloyInstance]
-> t m (AnyCd, [CdChangeAndCd])
getInstanceWithODs [StructuralWeakeningSet]
weakeningSets [StructuralWeakening]
_ [] =
[StructuralWeakeningSet] -> t m (AnyCd, [CdChangeAndCd])
tryNextWeakeningSet [StructuralWeakeningSet]
weakeningSets
getInstanceWithODs [StructuralWeakeningSet]
cs [StructuralWeakening]
structuralWeakenings (AlloyInstance
alloyInstance : [AlloyInstance]
alloyInstances) = do
GenericClassDiagramInstance String String
cdInstance <- AlloyInstance -> t m (GenericClassDiagramInstance String String)
forall (m :: * -> *).
MonadThrow m =>
AlloyInstance -> m (GenericClassDiagramInstance String String)
fromInstance AlloyInstance
alloyInstance t m (GenericClassDiagramInstance String String)
-> (GenericClassDiagramInstance String String
-> t m (GenericClassDiagramInstance String String))
-> t m (GenericClassDiagramInstance String String)
forall a b. t m a -> (a -> t m b) -> t m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= GenericClassDiagramInstance String String
-> t m (GenericClassDiagramInstance String String)
forall (m :: * -> *) className relationshipName.
(MonadThrow m, Ord className, Ord relationshipName) =>
GenericClassDiagramInstance className relationshipName
-> m (GenericClassDiagramInstance String String)
nameClassDiagramInstance
([StructuralWeakening]
shuffledStructuralWeakenings, [ChangeAndCd String String]
shuffledChangesAndCds) <-
[(StructuralWeakening, ChangeAndCd String String)]
-> ([StructuralWeakening], [ChangeAndCd String String])
forall a b. [(a, b)] -> ([a], [b])
unzip ([(StructuralWeakening, ChangeAndCd String String)]
-> ([StructuralWeakening], [ChangeAndCd String String]))
-> t m [(StructuralWeakening, ChangeAndCd String String)]
-> t m ([StructuralWeakening], [ChangeAndCd String String])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(StructuralWeakening, ChangeAndCd String String)]
-> t m [(StructuralWeakening, ChangeAndCd String String)]
forall (m :: * -> *) a. MonadRandom m => [a] -> m [a]
shuffleM ([StructuralWeakening]
-> [ChangeAndCd String String]
-> [(StructuralWeakening, ChangeAndCd String String)]
forall a b. [a] -> [b] -> [(a, b)]
zip [StructuralWeakening]
structuralWeakenings ([ChangeAndCd String String]
-> [(StructuralWeakening, ChangeAndCd String String)])
-> [ChangeAndCd String String]
-> [(StructuralWeakening, ChangeAndCd String String)]
forall a b. (a -> b) -> a -> b
$ GenericClassDiagramInstance String String
-> [ChangeAndCd String String]
forall className relationshipName.
GenericClassDiagramInstance className relationshipName
-> [ChangeAndCd className relationshipName]
instanceChangesAndCds GenericClassDiagramInstance String String
cdInstance)
let shuffledCdInstance :: GenericClassDiagramInstance String String
shuffledCdInstance = GenericClassDiagramInstance String String
cdInstance {
instanceChangesAndCds :: [ChangeAndCd String String]
instanceChangesAndCds = [ChangeAndCd String String]
shuffledChangesAndCds
}
let cd :: AnyCd
cd = GenericClassDiagramInstance String String -> AnyCd
forall className relationshipName.
GenericClassDiagramInstance className relationshipName
-> AnyClassDiagram className relationshipName
instanceClassDiagram GenericClassDiagramInstance String String
shuffledCdInstance
chs :: [ChangeAndCd String String]
chs = GenericClassDiagramInstance String String
-> [ChangeAndCd String String]
forall className relationshipName.
GenericClassDiagramInstance className relationshipName
-> [ChangeAndCd className relationshipName]
instanceChangesAndCds GenericClassDiagramInstance String String
shuffledCdInstance
[Maybe (Either (Change (AnyRelationship String String)) Od)]
hints <- (StructuralWeakening
-> ChangeAndCd String String
-> t m
(Maybe (Either (Change (AnyRelationship String String)) Od)))
-> [StructuralWeakening]
-> [ChangeAndCd String String]
-> t m [Maybe (Either (Change (AnyRelationship String String)) Od)]
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM StructuralWeakening
-> ChangeAndCd String String
-> t m (Maybe (Either (Change (AnyRelationship String String)) Od))
forall {m :: * -> *}.
(MonadAlloy m, MonadCatch m, MonadRandom m) =>
StructuralWeakening
-> ChangeAndCd String String
-> m (Maybe (Either (Change (AnyRelationship String String)) Od))
getOdOrImprovedCd [StructuralWeakening]
shuffledStructuralWeakenings [ChangeAndCd String String]
chs
case [Maybe (Either (Change (AnyRelationship String String)) Od)]
-> Maybe [Either (Change (AnyRelationship String String)) Od]
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
forall (f :: * -> *) a. Applicative f => [f a] -> f [a]
sequenceA [Maybe (Either (Change (AnyRelationship String String)) Od)]
hints of
Maybe [Either (Change (AnyRelationship String String)) Od]
Nothing -> [StructuralWeakeningSet]
-> [StructuralWeakening]
-> [AlloyInstance]
-> t m (AnyCd, [CdChangeAndCd])
getInstanceWithODs [StructuralWeakeningSet]
cs [StructuralWeakening]
structuralWeakenings [AlloyInstance]
alloyInstances
Just [Either (Change (AnyRelationship String String)) Od]
odsAndCds -> do
let odsAndCdWithArticle :: [Either
(Annotation ArticleToUse (Change (AnyRelationship String String)))
Od]
odsAndCdWithArticle = (Either (Change (AnyRelationship String String)) Od
-> Either
(Annotation ArticleToUse (Change (AnyRelationship String String)))
Od)
-> [Either (Change (AnyRelationship String String)) Od]
-> [Either
(Annotation ArticleToUse (Change (AnyRelationship String String)))
Od]
forall a b. (a -> b) -> [a] -> [b]
map ((Change (AnyRelationship String String)
-> Annotation
ArticleToUse (Change (AnyRelationship String String)))
-> Either (Change (AnyRelationship String String)) Od
-> Either
(Annotation ArticleToUse (Change (AnyRelationship String String)))
Od
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first Change (AnyRelationship String String)
-> Annotation ArticleToUse (Change (AnyRelationship String String))
forall {annotated}. annotated -> Annotation ArticleToUse annotated
addArticle) [Either (Change (AnyRelationship String String)) Od]
odsAndCds
chs' :: [AnnotatedChangeAndCd ArticleToUse String String]
chs' = (ChangeAndCd String String
-> AnnotatedChangeAndCd ArticleToUse String String)
-> [ChangeAndCd String String]
-> [AnnotatedChangeAndCd ArticleToUse String String]
forall a b. (a -> b) -> [a] -> [b]
map (ArticleToUse
-> ChangeAndCd String String
-> AnnotatedChangeAndCd ArticleToUse String String
forall annotation className relationshipName.
annotation
-> ChangeAndCd className relationshipName
-> AnnotatedChangeAndCd annotation className relationshipName
uniformlyAnnotateChangeAndCd ArticleToUse
article) [ChangeAndCd String String]
chs
(AnyCd, [CdChangeAndCd]) -> t m (AnyCd, [CdChangeAndCd])
forall a. a -> t m a
forall (f :: * -> *) a. Applicative f => a -> f a
return (AnyCd
cd, (Either
(Annotation ArticleToUse (Change (AnyRelationship String String)))
Od
-> AnnotatedChangeAndCd ArticleToUse String String
-> CdChangeAndCd)
-> [Either
(Annotation ArticleToUse (Change (AnyRelationship String String)))
Od]
-> [AnnotatedChangeAndCd ArticleToUse String String]
-> [CdChangeAndCd]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Either
(Annotation ArticleToUse (Change (AnyRelationship String String)))
Od
-> AnnotatedChangeAndCd ArticleToUse String String -> CdChangeAndCd
forall option forInvalidity forValidity.
Either forInvalidity forValidity
-> option -> InValidOption option forInvalidity forValidity
InValidOption [Either
(Annotation ArticleToUse (Change (AnyRelationship String String)))
Od]
odsAndCdWithArticle [AnnotatedChangeAndCd ArticleToUse String String]
chs')
addArticle :: annotated -> Annotation ArticleToUse annotated
addArticle = (annotated -> ArticleToUse -> Annotation ArticleToUse annotated
forall annotation annotated.
annotated -> annotation -> Annotation annotation annotated
`Annotation` ArticleToUse
article)
getOdOrImprovedCd :: StructuralWeakening
-> ChangeAndCd String String
-> m (Maybe (Either (Change (AnyRelationship String String)) Od))
getOdOrImprovedCd StructuralWeakening
structuralWeakenings ChangeAndCd String String
change
| StructuralWeakening -> Bool
isValidWeakening StructuralWeakening
structuralWeakenings
= do
Cd
cd <- AnyCd -> m Cd
forall className (m :: * -> *) relationshipName.
(Eq className, MonadThrow m, Show className, Show relationshipName,
Typeable className, Typeable relationshipName) =>
AnyClassDiagram className relationshipName
-> m (ClassDiagram className relationshipName)
toValidCd (AnyCd -> m Cd) -> AnyCd -> m Cd
forall a b. (a -> b) -> a -> b
$ ChangeAndCd String String -> AnyCd
forall className relationshipName.
ChangeAndCd className relationshipName
-> AnyClassDiagram className relationshipName
changeClassDiagram ChangeAndCd String String
change
(Od -> Either (Change (AnyRelationship String String)) Od)
-> Maybe Od
-> Maybe (Either (Change (AnyRelationship String String)) Od)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Od -> Either (Change (AnyRelationship String String)) Od
forall a b. b -> Either a b
Right (Maybe Od
-> Maybe (Either (Change (AnyRelationship String String)) Od))
-> m (Maybe Od)
-> m (Maybe (Either (Change (AnyRelationship String String)) Od))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Cd -> m (Maybe Od)
forall (m :: * -> *).
(MonadAlloy m, MonadCatch m, MonadRandom m) =>
Cd -> m (Maybe Od)
getOD Cd
cd
| Bool
otherwise = (Change (AnyRelationship String String)
-> Either (Change (AnyRelationship String String)) Od)
-> Maybe (Change (AnyRelationship String String))
-> Maybe (Either (Change (AnyRelationship String String)) Od)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Change (AnyRelationship String String)
-> Either (Change (AnyRelationship String String)) Od
forall a b. a -> Either a b
Left
(Maybe (Change (AnyRelationship String String))
-> Maybe (Either (Change (AnyRelationship String String)) Od))
-> m (Maybe (Change (AnyRelationship String String)))
-> m (Maybe (Either (Change (AnyRelationship String String)) Od))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> AnyCd
-> RelationshipProperties
-> m (Maybe (Change (AnyRelationship String String)))
forall {m :: * -> *}.
(MonadAlloy m, MonadThrow m) =>
AnyCd
-> RelationshipProperties
-> m (Maybe (Change (AnyRelationship String String)))
getImprovedCd (ChangeAndCd String String -> AnyCd
forall className relationshipName.
ChangeAndCd className relationshipName
-> AnyClassDiagram className relationshipName
changeClassDiagram ChangeAndCd String String
change) (StructuralWeakening -> RelationshipProperties
toProperty StructuralWeakening
structuralWeakenings)
getImprovedCd :: AnyCd
-> RelationshipProperties
-> m (Maybe (Change (AnyRelationship String String)))
getImprovedCd AnyCd
cd RelationshipProperties
properties = do
let alloyCode :: String
alloyCode = AnyCd
-> ClassConfig -> [CdMutation] -> RelationshipProperties -> String
Changes.transformImproveCd
AnyCd
cd
ClassConfig
config
[CdMutation
RemoveRelationship]
RelationshipProperties
properties
Maybe AlloyInstance
changes <- [AlloyInstance] -> Maybe AlloyInstance
forall a. [a] -> Maybe a
listToMaybe ([AlloyInstance] -> Maybe AlloyInstance)
-> m [AlloyInstance] -> m (Maybe AlloyInstance)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Integer -> Maybe Int -> String -> m [AlloyInstance]
forall (m :: * -> *).
MonadAlloy m =>
Maybe Integer -> Maybe Int -> String -> m [AlloyInstance]
getInstances (Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
1) Maybe Int
to String
alloyCode
(GenericClassDiagramInstance String String
-> Change (AnyRelationship String String))
-> Maybe (GenericClassDiagramInstance String String)
-> Maybe (Change (AnyRelationship String String))
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ChangeAndCd String String -> Change (AnyRelationship String String)
forall className relationshipName.
ChangeAndCd className relationshipName
-> Change (AnyRelationship className relationshipName)
relationshipChange (ChangeAndCd String String
-> Change (AnyRelationship String String))
-> (GenericClassDiagramInstance String String
-> ChangeAndCd String String)
-> GenericClassDiagramInstance String String
-> Change (AnyRelationship String String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ChangeAndCd String String] -> ChangeAndCd String String
forall a. HasCallStack => [a] -> a
head ([ChangeAndCd String String] -> ChangeAndCd String String)
-> (GenericClassDiagramInstance String String
-> [ChangeAndCd String String])
-> GenericClassDiagramInstance String String
-> ChangeAndCd String String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenericClassDiagramInstance String String
-> [ChangeAndCd String String]
forall className relationshipName.
GenericClassDiagramInstance className relationshipName
-> [ChangeAndCd className relationshipName]
instanceChangesAndCds)
(Maybe (GenericClassDiagramInstance String String)
-> Maybe (Change (AnyRelationship String String)))
-> m (Maybe (GenericClassDiagramInstance String String))
-> m (Maybe (Change (AnyRelationship String String)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (AlloyInstance -> m (GenericClassDiagramInstance String String))
-> Maybe AlloyInstance
-> m (Maybe (GenericClassDiagramInstance String String))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Maybe a -> f (Maybe b)
traverse AlloyInstance -> m (GenericClassDiagramInstance String String)
forall (m :: * -> *).
MonadThrow m =>
AlloyInstance -> m (GenericClassDiagramInstance String String)
fromInstanceWithPredefinedNames Maybe AlloyInstance
changes
getOD :: (MonadAlloy m, MonadCatch m, MonadRandom m) => Cd -> m (Maybe Od)
getOD :: forall (m :: * -> *).
(MonadAlloy m, MonadCatch m, MonadRandom m) =>
Cd -> m (Maybe Od)
getOD Cd
cd = do
let maxNumberOfObjects :: ObjectConfig
maxNumberOfObjects = Int -> ObjectConfig
maxObjects (Int -> ObjectConfig) -> Int -> ObjectConfig
forall a b. (a -> b) -> a -> b
$ (Int, Int) -> Int
forall a b. (a, b) -> b
snd ((Int, Int) -> Int) -> (Int, Int) -> Int
forall a b. (a -> b) -> a -> b
$ ClassConfig -> (Int, Int)
classLimits ClassConfig
config
parts :: Parts
parts = LinguisticReuse
-> Cd
-> Maybe [String]
-> [String]
-> ObjectConfig
-> ObjectProperties
-> String
-> String
-> Parts
transform
(ExtendsAnd -> LinguisticReuse
ExtendsAnd ExtendsAnd
FieldPlacement)
Cd
cd
Maybe [String]
forall a. Maybe a
Nothing
[]
ObjectConfig
maxNumberOfObjects
ObjectProperties
objectProperties
String
""
String
""
command :: String
command = String
-> Maybe [String]
-> Int
-> ObjectConfig
-> [Relationship String String]
-> String
forall a b.
String
-> Maybe [String]
-> Int
-> ObjectConfig
-> [Relationship a b]
-> String
createRunCommand
String
"cd"
([String] -> Maybe [String]
forall a. a -> Maybe a
Just ([String] -> Maybe [String]) -> [String] -> Maybe [String]
forall a b. (a -> b) -> a -> b
$ Cd -> [String]
forall className relationshipName.
ClassDiagram className relationshipName -> [className]
classNames Cd
cd)
([String] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([String] -> Int) -> [String] -> Int
forall a b. (a -> b) -> a -> b
$ Cd -> [String]
forall className relationshipName.
ClassDiagram className relationshipName -> [className]
classNames Cd
cd)
ObjectConfig
maxNumberOfObjects
(Cd -> [Relationship String String]
forall className relationshipName.
ClassDiagram className relationshipName
-> [Relationship className relationshipName]
relationships Cd
cd)
Maybe AlloyInstance
od <- [AlloyInstance] -> Maybe AlloyInstance
forall a. [a] -> Maybe a
listToMaybe
([AlloyInstance] -> Maybe AlloyInstance)
-> m [AlloyInstance] -> m (Maybe AlloyInstance)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Integer -> Maybe Int -> String -> m [AlloyInstance]
forall (m :: * -> *).
MonadAlloy m =>
Maybe Integer -> Maybe Int -> String -> m [AlloyInstance]
getInstances (Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
1) Maybe Int
to (Parts -> String
combineParts Parts
parts String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
command)
Maybe Od
od' <- Maybe AlloyInstance -> (AlloyInstance -> m Od) -> m (Maybe Od)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM Maybe AlloyInstance
od ((AlloyInstance -> m Od) -> m (Maybe Od))
-> (AlloyInstance -> m Od) -> m (Maybe Od)
forall a b. (a -> b) -> a -> b
$ Maybe [String] -> [String] -> AlloyInstance -> m Od
forall (m :: * -> *).
MonadCatch m =>
Maybe [String] -> [String] -> AlloyInstance -> m Od
alloyInstanceToOd
([String] -> Maybe [String]
forall a. a -> Maybe a
Just ([String] -> Maybe [String]) -> [String] -> Maybe [String]
forall a b. (a -> b) -> a -> b
$ Cd -> [String]
forall className relationshipName.
ClassDiagram className relationshipName -> [className]
classNames Cd
cd)
([String] -> AlloyInstance -> m Od)
-> [String] -> AlloyInstance -> m Od
forall a b. (a -> b) -> a -> b
$ (Relationship String String -> Maybe String)
-> [Relationship String String] -> [String]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Relationship String String -> Maybe String
forall c r. Relationship c r -> Maybe r
relationshipName ([Relationship String String] -> [String])
-> [Relationship String String] -> [String]
forall a b. (a -> b) -> a -> b
$ Cd -> [Relationship String String]
forall className relationshipName.
ClassDiagram className relationshipName
-> [Relationship className relationshipName]
relationships Cd
cd
(Od -> m Od) -> Maybe Od -> m (Maybe Od)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Maybe a -> m (Maybe b)
mapM (Rational -> Od -> m Od
forall (m :: * -> *) className relationshipName linkLabel.
MonadRandom m =>
Rational
-> ObjectDiagram className relationshipName linkLabel
-> m (ObjectDiagram className relationshipName linkLabel)
anonymiseObjects (ObjectProperties -> Rational
anonymousObjectProportion ObjectProperties
objectProperties)) Maybe Od
od'
allStructuralWeakenings :: AllowedProperties -> [StructuralWeakening]
allStructuralWeakenings :: AllowedProperties -> [StructuralWeakening]
allStructuralWeakenings AllowedProperties
c =
AllowedProperties -> [StructuralWeakening]
legalStructuralWeakenings AllowedProperties
c [StructuralWeakening]
-> [StructuralWeakening] -> [StructuralWeakening]
forall a. [a] -> [a] -> [a]
++ AllowedProperties -> [StructuralWeakening]
illegalStructuralWeakenings AllowedProperties
c
data Weakening
= None
| Add !AdditiveWeakening
| Force !ForcibleWeakening
deriving (Weakening -> Weakening -> Bool
(Weakening -> Weakening -> Bool)
-> (Weakening -> Weakening -> Bool) -> Eq Weakening
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Weakening -> Weakening -> Bool
== :: Weakening -> Weakening -> Bool
$c/= :: Weakening -> Weakening -> Bool
/= :: Weakening -> Weakening -> Bool
Eq, Eq Weakening
Eq Weakening
-> (Weakening -> Weakening -> Ordering)
-> (Weakening -> Weakening -> Bool)
-> (Weakening -> Weakening -> Bool)
-> (Weakening -> Weakening -> Bool)
-> (Weakening -> Weakening -> Bool)
-> (Weakening -> Weakening -> Weakening)
-> (Weakening -> Weakening -> Weakening)
-> Ord Weakening
Weakening -> Weakening -> Bool
Weakening -> Weakening -> Ordering
Weakening -> Weakening -> Weakening
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Weakening -> Weakening -> Ordering
compare :: Weakening -> Weakening -> Ordering
$c< :: Weakening -> Weakening -> Bool
< :: Weakening -> Weakening -> Bool
$c<= :: Weakening -> Weakening -> Bool
<= :: Weakening -> Weakening -> Bool
$c> :: Weakening -> Weakening -> Bool
> :: Weakening -> Weakening -> Bool
$c>= :: Weakening -> Weakening -> Bool
>= :: Weakening -> Weakening -> Bool
$cmax :: Weakening -> Weakening -> Weakening
max :: Weakening -> Weakening -> Weakening
$cmin :: Weakening -> Weakening -> Weakening
min :: Weakening -> Weakening -> Weakening
Ord, Int -> Weakening -> ShowS
[Weakening] -> ShowS
Weakening -> String
(Int -> Weakening -> ShowS)
-> (Weakening -> String)
-> ([Weakening] -> ShowS)
-> Show Weakening
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Weakening -> ShowS
showsPrec :: Int -> Weakening -> ShowS
$cshow :: Weakening -> String
show :: Weakening -> String
$cshowList :: [Weakening] -> ShowS
showList :: [Weakening] -> ShowS
Show)
data AdditiveWeakening
= InvalidInheritance
| SelfInheritance
| SelfRelationship
| WrongAssociation
| WrongComposition
deriving (AdditiveWeakening -> AdditiveWeakening -> Bool
(AdditiveWeakening -> AdditiveWeakening -> Bool)
-> (AdditiveWeakening -> AdditiveWeakening -> Bool)
-> Eq AdditiveWeakening
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AdditiveWeakening -> AdditiveWeakening -> Bool
== :: AdditiveWeakening -> AdditiveWeakening -> Bool
$c/= :: AdditiveWeakening -> AdditiveWeakening -> Bool
/= :: AdditiveWeakening -> AdditiveWeakening -> Bool
Eq, Eq AdditiveWeakening
Eq AdditiveWeakening
-> (AdditiveWeakening -> AdditiveWeakening -> Ordering)
-> (AdditiveWeakening -> AdditiveWeakening -> Bool)
-> (AdditiveWeakening -> AdditiveWeakening -> Bool)
-> (AdditiveWeakening -> AdditiveWeakening -> Bool)
-> (AdditiveWeakening -> AdditiveWeakening -> Bool)
-> (AdditiveWeakening -> AdditiveWeakening -> AdditiveWeakening)
-> (AdditiveWeakening -> AdditiveWeakening -> AdditiveWeakening)
-> Ord AdditiveWeakening
AdditiveWeakening -> AdditiveWeakening -> Bool
AdditiveWeakening -> AdditiveWeakening -> Ordering
AdditiveWeakening -> AdditiveWeakening -> AdditiveWeakening
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AdditiveWeakening -> AdditiveWeakening -> Ordering
compare :: AdditiveWeakening -> AdditiveWeakening -> Ordering
$c< :: AdditiveWeakening -> AdditiveWeakening -> Bool
< :: AdditiveWeakening -> AdditiveWeakening -> Bool
$c<= :: AdditiveWeakening -> AdditiveWeakening -> Bool
<= :: AdditiveWeakening -> AdditiveWeakening -> Bool
$c> :: AdditiveWeakening -> AdditiveWeakening -> Bool
> :: AdditiveWeakening -> AdditiveWeakening -> Bool
$c>= :: AdditiveWeakening -> AdditiveWeakening -> Bool
>= :: AdditiveWeakening -> AdditiveWeakening -> Bool
$cmax :: AdditiveWeakening -> AdditiveWeakening -> AdditiveWeakening
max :: AdditiveWeakening -> AdditiveWeakening -> AdditiveWeakening
$cmin :: AdditiveWeakening -> AdditiveWeakening -> AdditiveWeakening
min :: AdditiveWeakening -> AdditiveWeakening -> AdditiveWeakening
Ord, Int -> AdditiveWeakening -> ShowS
[AdditiveWeakening] -> ShowS
AdditiveWeakening -> String
(Int -> AdditiveWeakening -> ShowS)
-> (AdditiveWeakening -> String)
-> ([AdditiveWeakening] -> ShowS)
-> Show AdditiveWeakening
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AdditiveWeakening -> ShowS
showsPrec :: Int -> AdditiveWeakening -> ShowS
$cshow :: AdditiveWeakening -> String
show :: AdditiveWeakening -> String
$cshowList :: [AdditiveWeakening] -> ShowS
showList :: [AdditiveWeakening] -> ShowS
Show)
data ForcibleWeakening
= CompositionCycles
| DoubleRelationships
| InheritanceCycles
| ReverseInheritances
| ReverseRelationships
deriving (ForcibleWeakening -> ForcibleWeakening -> Bool
(ForcibleWeakening -> ForcibleWeakening -> Bool)
-> (ForcibleWeakening -> ForcibleWeakening -> Bool)
-> Eq ForcibleWeakening
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ForcibleWeakening -> ForcibleWeakening -> Bool
== :: ForcibleWeakening -> ForcibleWeakening -> Bool
$c/= :: ForcibleWeakening -> ForcibleWeakening -> Bool
/= :: ForcibleWeakening -> ForcibleWeakening -> Bool
Eq, Eq ForcibleWeakening
Eq ForcibleWeakening
-> (ForcibleWeakening -> ForcibleWeakening -> Ordering)
-> (ForcibleWeakening -> ForcibleWeakening -> Bool)
-> (ForcibleWeakening -> ForcibleWeakening -> Bool)
-> (ForcibleWeakening -> ForcibleWeakening -> Bool)
-> (ForcibleWeakening -> ForcibleWeakening -> Bool)
-> (ForcibleWeakening -> ForcibleWeakening -> ForcibleWeakening)
-> (ForcibleWeakening -> ForcibleWeakening -> ForcibleWeakening)
-> Ord ForcibleWeakening
ForcibleWeakening -> ForcibleWeakening -> Bool
ForcibleWeakening -> ForcibleWeakening -> Ordering
ForcibleWeakening -> ForcibleWeakening -> ForcibleWeakening
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ForcibleWeakening -> ForcibleWeakening -> Ordering
compare :: ForcibleWeakening -> ForcibleWeakening -> Ordering
$c< :: ForcibleWeakening -> ForcibleWeakening -> Bool
< :: ForcibleWeakening -> ForcibleWeakening -> Bool
$c<= :: ForcibleWeakening -> ForcibleWeakening -> Bool
<= :: ForcibleWeakening -> ForcibleWeakening -> Bool
$c> :: ForcibleWeakening -> ForcibleWeakening -> Bool
> :: ForcibleWeakening -> ForcibleWeakening -> Bool
$c>= :: ForcibleWeakening -> ForcibleWeakening -> Bool
>= :: ForcibleWeakening -> ForcibleWeakening -> Bool
$cmax :: ForcibleWeakening -> ForcibleWeakening -> ForcibleWeakening
max :: ForcibleWeakening -> ForcibleWeakening -> ForcibleWeakening
$cmin :: ForcibleWeakening -> ForcibleWeakening -> ForcibleWeakening
min :: ForcibleWeakening -> ForcibleWeakening -> ForcibleWeakening
Ord, Int -> ForcibleWeakening -> ShowS
[ForcibleWeakening] -> ShowS
ForcibleWeakening -> String
(Int -> ForcibleWeakening -> ShowS)
-> (ForcibleWeakening -> String)
-> ([ForcibleWeakening] -> ShowS)
-> Show ForcibleWeakening
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ForcibleWeakening -> ShowS
showsPrec :: Int -> ForcibleWeakening -> ShowS
$cshow :: ForcibleWeakening -> String
show :: ForcibleWeakening -> String
$cshowList :: [ForcibleWeakening] -> ShowS
showList :: [ForcibleWeakening] -> ShowS
Show)
mergeWeakenings :: [Weakening] -> [Weakening] -> [Weakening]
mergeWeakenings :: [Weakening] -> [Weakening] -> [Weakening]
mergeWeakenings [] [Weakening]
ys = [Weakening]
ys
mergeWeakenings [Weakening]
xs [] = [Weakening]
xs
mergeWeakenings xs :: [Weakening]
xs@(Weakening
_:[Weakening]
_) (Weakening
None:[Weakening]
ys) = [Weakening] -> [Weakening] -> [Weakening]
mergeWeakenings [Weakening]
xs [Weakening]
ys
mergeWeakenings (Weakening
None:[Weakening]
xs) ys :: [Weakening]
ys@(Weakening
_:[Weakening]
_) = [Weakening] -> [Weakening] -> [Weakening]
mergeWeakenings [Weakening]
xs [Weakening]
ys
mergeWeakenings keeps :: [Weakening]
keeps@(x :: Weakening
x@Force {}:[Weakening]
xs) others :: [Weakening]
others@(y :: Weakening
y@Force {}:[Weakening]
ys)
| Weakening
x Weakening -> Weakening -> Bool
forall a. Eq a => a -> a -> Bool
== Weakening
y = [Weakening] -> [Weakening] -> [Weakening]
mergeWeakenings [Weakening]
keeps [Weakening]
ys
| Weakening
x Weakening -> Weakening -> Bool
forall a. Ord a => a -> a -> Bool
< Weakening
y = Weakening
x Weakening -> [Weakening] -> [Weakening]
forall a. a -> [a] -> [a]
: [Weakening] -> [Weakening] -> [Weakening]
mergeWeakenings [Weakening]
xs [Weakening]
others
| Bool
otherwise = Weakening
y Weakening -> [Weakening] -> [Weakening]
forall a. a -> [a] -> [a]
: [Weakening] -> [Weakening] -> [Weakening]
mergeWeakenings [Weakening]
keeps [Weakening]
ys
mergeWeakenings keeps :: [Weakening]
keeps@(Weakening
x:[Weakening]
xs) others :: [Weakening]
others@(Weakening
y:[Weakening]
ys)
| Weakening
x Weakening -> Weakening -> Bool
forall a. Ord a => a -> a -> Bool
<= Weakening
y = Weakening
x Weakening -> [Weakening] -> [Weakening]
forall a. a -> [a] -> [a]
: [Weakening] -> [Weakening] -> [Weakening]
mergeWeakenings [Weakening]
xs [Weakening]
others
| Bool
otherwise = Weakening
y Weakening -> [Weakening] -> [Weakening]
forall a. a -> [a] -> [a]
: [Weakening] -> [Weakening] -> [Weakening]
mergeWeakenings [Weakening]
keeps [Weakening]
ys
noStructuralWeakening :: StructuralWeakening
noStructuralWeakening :: StructuralWeakening
noStructuralWeakening = [Weakening]
-> (RelationshipProperties -> RelationshipProperties)
-> (Bool -> Bool)
-> StructuralWeakening
StructuralWeakening [Weakening
None] RelationshipProperties -> RelationshipProperties
forall a. a -> a
id Bool -> Bool
forall a. a -> a
id
infixl 9 .&.
(.&.) :: StructuralWeakening -> StructuralWeakening -> StructuralWeakening
StructuralWeakening [Weakening]
n1 RelationshipProperties -> RelationshipProperties
o1 Bool -> Bool
v1 .&. :: StructuralWeakening -> StructuralWeakening -> StructuralWeakening
.&. StructuralWeakening [Weakening]
n2 RelationshipProperties -> RelationshipProperties
o2 Bool -> Bool
v2 =
[Weakening]
-> (RelationshipProperties -> RelationshipProperties)
-> (Bool -> Bool)
-> StructuralWeakening
StructuralWeakening
([Weakening] -> [Weakening] -> [Weakening]
mergeWeakenings [Weakening]
n1 [Weakening]
n2)
(RelationshipProperties -> RelationshipProperties
o1 (RelationshipProperties -> RelationshipProperties)
-> (RelationshipProperties -> RelationshipProperties)
-> RelationshipProperties
-> RelationshipProperties
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RelationshipProperties -> RelationshipProperties
o2)
(Bool -> Bool
v1 (Bool -> Bool) -> (Bool -> Bool) -> Bool -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Bool
v2)
legalStructuralWeakenings :: AllowedProperties -> [StructuralWeakening]
legalStructuralWeakenings :: AllowedProperties -> [StructuralWeakening]
legalStructuralWeakenings AllowedProperties
allowed = StructuralWeakening
noStructuralWeakening StructuralWeakening
-> [StructuralWeakening] -> [StructuralWeakening]
forall a. a -> [a] -> [a]
: [
[Weakening]
-> (RelationshipProperties -> RelationshipProperties)
-> (Bool -> Bool)
-> StructuralWeakening
StructuralWeakening [AdditiveWeakening -> Weakening
Add AdditiveWeakening
SelfRelationship] RelationshipProperties -> RelationshipProperties
addSelfRelationships Bool -> Bool
forall a. a -> a
id
| AllowedProperties -> Bool
selfRelationships AllowedProperties
allowed] [StructuralWeakening]
-> [StructuralWeakening] -> [StructuralWeakening]
forall a. [a] -> [a] -> [a]
++ [
[Weakening]
-> (RelationshipProperties -> RelationshipProperties)
-> (Bool -> Bool)
-> StructuralWeakening
StructuralWeakening [ForcibleWeakening -> Weakening
Force ForcibleWeakening
DoubleRelationships] RelationshipProperties -> RelationshipProperties
withDoubleRelationships Bool -> Bool
forall a. a -> a
id
| AllowedProperties -> Bool
doubleRelationships AllowedProperties
allowed] [StructuralWeakening]
-> [StructuralWeakening] -> [StructuralWeakening]
forall a. [a] -> [a] -> [a]
++ [
[Weakening]
-> (RelationshipProperties -> RelationshipProperties)
-> (Bool -> Bool)
-> StructuralWeakening
StructuralWeakening [ForcibleWeakening -> Weakening
Force ForcibleWeakening
ReverseRelationships] RelationshipProperties -> RelationshipProperties
withReverseRelationships Bool -> Bool
forall a. a -> a
id
| AllowedProperties -> Bool
reverseRelationships AllowedProperties
allowed]
where
addSelfRelationships :: RelationshipProperties -> RelationshipProperties
addSelfRelationships :: RelationshipProperties -> RelationshipProperties
addSelfRelationships config :: RelationshipProperties
config@RelationshipProperties {Bool
Int
Maybe Bool
invalidInheritances :: Int
wrongNonInheritances :: Int
wrongCompositions :: Int
selfRelationshipsAmount :: Int
selfInheritancesAmount :: Int
hasDoubleRelationships :: Maybe Bool
hasReverseRelationships :: Maybe Bool
hasReverseInheritances :: Bool
hasMultipleInheritances :: Maybe Bool
hasNonTrivialInheritanceCycles :: Bool
hasCompositionCycles :: Bool
hasCompositionsPreventingParts :: Maybe Bool
hasThickEdges :: Maybe Bool
invalidInheritances :: RelationshipProperties -> Int
wrongNonInheritances :: RelationshipProperties -> Int
wrongCompositions :: RelationshipProperties -> Int
selfRelationshipsAmount :: RelationshipProperties -> Int
selfInheritancesAmount :: RelationshipProperties -> Int
hasDoubleRelationships :: RelationshipProperties -> Maybe Bool
hasReverseRelationships :: RelationshipProperties -> Maybe Bool
hasReverseInheritances :: RelationshipProperties -> Bool
hasMultipleInheritances :: RelationshipProperties -> Maybe Bool
hasNonTrivialInheritanceCycles :: RelationshipProperties -> Bool
hasCompositionCycles :: RelationshipProperties -> Bool
hasCompositionsPreventingParts :: RelationshipProperties -> Maybe Bool
hasThickEdges :: RelationshipProperties -> Maybe Bool
..}
= RelationshipProperties
config { selfRelationshipsAmount :: Int
selfRelationshipsAmount = Int
selfRelationshipsAmount Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 }
withDoubleRelationships :: RelationshipProperties -> RelationshipProperties
withDoubleRelationships :: RelationshipProperties -> RelationshipProperties
withDoubleRelationships RelationshipProperties
config
= RelationshipProperties
config { hasDoubleRelationships :: Maybe Bool
hasDoubleRelationships = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True }
withReverseRelationships :: RelationshipProperties -> RelationshipProperties
withReverseRelationships :: RelationshipProperties -> RelationshipProperties
withReverseRelationships RelationshipProperties
config
= RelationshipProperties
config { hasReverseRelationships :: Maybe Bool
hasReverseRelationships = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True }
illegalStructuralWeakenings :: AllowedProperties -> [StructuralWeakening]
illegalStructuralWeakenings :: AllowedProperties -> [StructuralWeakening]
illegalStructuralWeakenings AllowedProperties
allowed = (((Bool -> Bool) -> StructuralWeakening) -> StructuralWeakening)
-> [(Bool -> Bool) -> StructuralWeakening] -> [StructuralWeakening]
forall a b. (a -> b) -> [a] -> [b]
map (((Bool -> Bool) -> StructuralWeakening)
-> (Bool -> Bool) -> StructuralWeakening
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> Bool
forall a b. a -> b -> a
const Bool
False) ([(Bool -> Bool) -> StructuralWeakening] -> [StructuralWeakening])
-> [(Bool -> Bool) -> StructuralWeakening] -> [StructuralWeakening]
forall a b. (a -> b) -> a -> b
$ [
[Weakening]
-> (RelationshipProperties -> RelationshipProperties)
-> (Bool -> Bool)
-> StructuralWeakening
StructuralWeakening [AdditiveWeakening -> Weakening
Add AdditiveWeakening
InvalidInheritance] RelationshipProperties -> RelationshipProperties
addInvalidInheritances
| AllowedProperties -> Bool
invalidInheritanceLimits AllowedProperties
allowed] [(Bool -> Bool) -> StructuralWeakening]
-> [(Bool -> Bool) -> StructuralWeakening]
-> [(Bool -> Bool) -> StructuralWeakening]
forall a. [a] -> [a] -> [a]
++ [
[Weakening]
-> (RelationshipProperties -> RelationshipProperties)
-> (Bool -> Bool)
-> StructuralWeakening
StructuralWeakening [AdditiveWeakening -> Weakening
Add AdditiveWeakening
WrongAssociation] RelationshipProperties -> RelationshipProperties
addWrongNonInheritances
| AllowedProperties -> Bool
wrongAssociationLimits AllowedProperties
allowed] [(Bool -> Bool) -> StructuralWeakening]
-> [(Bool -> Bool) -> StructuralWeakening]
-> [(Bool -> Bool) -> StructuralWeakening]
forall a. [a] -> [a] -> [a]
++ [
[Weakening]
-> (RelationshipProperties -> RelationshipProperties)
-> (Bool -> Bool)
-> StructuralWeakening
StructuralWeakening [AdditiveWeakening -> Weakening
Add AdditiveWeakening
WrongComposition] RelationshipProperties -> RelationshipProperties
addWrongCompositions
| AllowedProperties -> Bool
wrongCompositionLimits AllowedProperties
allowed] [(Bool -> Bool) -> StructuralWeakening]
-> [(Bool -> Bool) -> StructuralWeakening]
-> [(Bool -> Bool) -> StructuralWeakening]
forall a. [a] -> [a] -> [a]
++ [
[Weakening]
-> (RelationshipProperties -> RelationshipProperties)
-> (Bool -> Bool)
-> StructuralWeakening
StructuralWeakening [ForcibleWeakening -> Weakening
Force ForcibleWeakening
InheritanceCycles] RelationshipProperties -> RelationshipProperties
withNonTrivialInheritanceCycles
| AllowedProperties -> Bool
inheritanceCycles AllowedProperties
allowed] [(Bool -> Bool) -> StructuralWeakening]
-> [(Bool -> Bool) -> StructuralWeakening]
-> [(Bool -> Bool) -> StructuralWeakening]
forall a. [a] -> [a] -> [a]
++ [
[Weakening]
-> (RelationshipProperties -> RelationshipProperties)
-> (Bool -> Bool)
-> StructuralWeakening
StructuralWeakening [ForcibleWeakening -> Weakening
Force ForcibleWeakening
ReverseInheritances] RelationshipProperties -> RelationshipProperties
withReverseInheritances
| AllowedProperties -> Bool
reverseInheritances AllowedProperties
allowed] [(Bool -> Bool) -> StructuralWeakening]
-> [(Bool -> Bool) -> StructuralWeakening]
-> [(Bool -> Bool) -> StructuralWeakening]
forall a. [a] -> [a] -> [a]
++ [
[Weakening]
-> (RelationshipProperties -> RelationshipProperties)
-> (Bool -> Bool)
-> StructuralWeakening
StructuralWeakening [AdditiveWeakening -> Weakening
Add AdditiveWeakening
SelfInheritance] RelationshipProperties -> RelationshipProperties
addSelfInheritance
| AllowedProperties -> Bool
selfInheritances AllowedProperties
allowed] [(Bool -> Bool) -> StructuralWeakening]
-> [(Bool -> Bool) -> StructuralWeakening]
-> [(Bool -> Bool) -> StructuralWeakening]
forall a. [a] -> [a] -> [a]
++ [
[Weakening]
-> (RelationshipProperties -> RelationshipProperties)
-> (Bool -> Bool)
-> StructuralWeakening
StructuralWeakening [ForcibleWeakening -> Weakening
Force ForcibleWeakening
CompositionCycles] RelationshipProperties -> RelationshipProperties
withCompositionCycles
| AllowedProperties -> Bool
compositionCycles AllowedProperties
allowed]
where
addInvalidInheritances :: RelationshipProperties -> RelationshipProperties
addInvalidInheritances :: RelationshipProperties -> RelationshipProperties
addInvalidInheritances config :: RelationshipProperties
config@RelationshipProperties {Bool
Int
Maybe Bool
invalidInheritances :: RelationshipProperties -> Int
wrongNonInheritances :: RelationshipProperties -> Int
wrongCompositions :: RelationshipProperties -> Int
selfRelationshipsAmount :: RelationshipProperties -> Int
selfInheritancesAmount :: RelationshipProperties -> Int
hasDoubleRelationships :: RelationshipProperties -> Maybe Bool
hasReverseRelationships :: RelationshipProperties -> Maybe Bool
hasReverseInheritances :: RelationshipProperties -> Bool
hasMultipleInheritances :: RelationshipProperties -> Maybe Bool
hasNonTrivialInheritanceCycles :: RelationshipProperties -> Bool
hasCompositionCycles :: RelationshipProperties -> Bool
hasCompositionsPreventingParts :: RelationshipProperties -> Maybe Bool
hasThickEdges :: RelationshipProperties -> Maybe Bool
invalidInheritances :: Int
wrongNonInheritances :: Int
wrongCompositions :: Int
selfRelationshipsAmount :: Int
selfInheritancesAmount :: Int
hasDoubleRelationships :: Maybe Bool
hasReverseRelationships :: Maybe Bool
hasReverseInheritances :: Bool
hasMultipleInheritances :: Maybe Bool
hasNonTrivialInheritanceCycles :: Bool
hasCompositionCycles :: Bool
hasCompositionsPreventingParts :: Maybe Bool
hasThickEdges :: Maybe Bool
..}
= RelationshipProperties
config { invalidInheritances :: Int
invalidInheritances = Int
invalidInheritances Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 }
addWrongNonInheritances :: RelationshipProperties -> RelationshipProperties
addWrongNonInheritances :: RelationshipProperties -> RelationshipProperties
addWrongNonInheritances config :: RelationshipProperties
config@RelationshipProperties {Bool
Int
Maybe Bool
invalidInheritances :: RelationshipProperties -> Int
wrongNonInheritances :: RelationshipProperties -> Int
wrongCompositions :: RelationshipProperties -> Int
selfRelationshipsAmount :: RelationshipProperties -> Int
selfInheritancesAmount :: RelationshipProperties -> Int
hasDoubleRelationships :: RelationshipProperties -> Maybe Bool
hasReverseRelationships :: RelationshipProperties -> Maybe Bool
hasReverseInheritances :: RelationshipProperties -> Bool
hasMultipleInheritances :: RelationshipProperties -> Maybe Bool
hasNonTrivialInheritanceCycles :: RelationshipProperties -> Bool
hasCompositionCycles :: RelationshipProperties -> Bool
hasCompositionsPreventingParts :: RelationshipProperties -> Maybe Bool
hasThickEdges :: RelationshipProperties -> Maybe Bool
invalidInheritances :: Int
wrongNonInheritances :: Int
wrongCompositions :: Int
selfRelationshipsAmount :: Int
selfInheritancesAmount :: Int
hasDoubleRelationships :: Maybe Bool
hasReverseRelationships :: Maybe Bool
hasReverseInheritances :: Bool
hasMultipleInheritances :: Maybe Bool
hasNonTrivialInheritanceCycles :: Bool
hasCompositionCycles :: Bool
hasCompositionsPreventingParts :: Maybe Bool
hasThickEdges :: Maybe Bool
..}
= RelationshipProperties
config { wrongNonInheritances :: Int
wrongNonInheritances = Int
wrongNonInheritances Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 }
addWrongCompositions :: RelationshipProperties -> RelationshipProperties
addWrongCompositions :: RelationshipProperties -> RelationshipProperties
addWrongCompositions config :: RelationshipProperties
config@RelationshipProperties {Bool
Int
Maybe Bool
invalidInheritances :: RelationshipProperties -> Int
wrongNonInheritances :: RelationshipProperties -> Int
wrongCompositions :: RelationshipProperties -> Int
selfRelationshipsAmount :: RelationshipProperties -> Int
selfInheritancesAmount :: RelationshipProperties -> Int
hasDoubleRelationships :: RelationshipProperties -> Maybe Bool
hasReverseRelationships :: RelationshipProperties -> Maybe Bool
hasReverseInheritances :: RelationshipProperties -> Bool
hasMultipleInheritances :: RelationshipProperties -> Maybe Bool
hasNonTrivialInheritanceCycles :: RelationshipProperties -> Bool
hasCompositionCycles :: RelationshipProperties -> Bool
hasCompositionsPreventingParts :: RelationshipProperties -> Maybe Bool
hasThickEdges :: RelationshipProperties -> Maybe Bool
invalidInheritances :: Int
wrongNonInheritances :: Int
wrongCompositions :: Int
selfRelationshipsAmount :: Int
selfInheritancesAmount :: Int
hasDoubleRelationships :: Maybe Bool
hasReverseRelationships :: Maybe Bool
hasReverseInheritances :: Bool
hasMultipleInheritances :: Maybe Bool
hasNonTrivialInheritanceCycles :: Bool
hasCompositionCycles :: Bool
hasCompositionsPreventingParts :: Maybe Bool
hasThickEdges :: Maybe Bool
..}
= RelationshipProperties
config { wrongCompositions :: Int
wrongCompositions = Int
wrongCompositions Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 }
addSelfInheritance :: RelationshipProperties -> RelationshipProperties
addSelfInheritance :: RelationshipProperties -> RelationshipProperties
addSelfInheritance config :: RelationshipProperties
config@RelationshipProperties {Bool
Int
Maybe Bool
invalidInheritances :: RelationshipProperties -> Int
wrongNonInheritances :: RelationshipProperties -> Int
wrongCompositions :: RelationshipProperties -> Int
selfRelationshipsAmount :: RelationshipProperties -> Int
selfInheritancesAmount :: RelationshipProperties -> Int
hasDoubleRelationships :: RelationshipProperties -> Maybe Bool
hasReverseRelationships :: RelationshipProperties -> Maybe Bool
hasReverseInheritances :: RelationshipProperties -> Bool
hasMultipleInheritances :: RelationshipProperties -> Maybe Bool
hasNonTrivialInheritanceCycles :: RelationshipProperties -> Bool
hasCompositionCycles :: RelationshipProperties -> Bool
hasCompositionsPreventingParts :: RelationshipProperties -> Maybe Bool
hasThickEdges :: RelationshipProperties -> Maybe Bool
invalidInheritances :: Int
wrongNonInheritances :: Int
wrongCompositions :: Int
selfRelationshipsAmount :: Int
selfInheritancesAmount :: Int
hasDoubleRelationships :: Maybe Bool
hasReverseRelationships :: Maybe Bool
hasReverseInheritances :: Bool
hasMultipleInheritances :: Maybe Bool
hasNonTrivialInheritanceCycles :: Bool
hasCompositionCycles :: Bool
hasCompositionsPreventingParts :: Maybe Bool
hasThickEdges :: Maybe Bool
..}
= RelationshipProperties
config { selfInheritancesAmount :: Int
selfInheritancesAmount = Int
selfInheritancesAmount Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 }
withReverseInheritances :: RelationshipProperties -> RelationshipProperties
withReverseInheritances :: RelationshipProperties -> RelationshipProperties
withReverseInheritances RelationshipProperties
config
= RelationshipProperties
config { hasReverseInheritances :: Bool
hasReverseInheritances = Bool
True }
withNonTrivialInheritanceCycles
:: RelationshipProperties
-> RelationshipProperties
withNonTrivialInheritanceCycles :: RelationshipProperties -> RelationshipProperties
withNonTrivialInheritanceCycles RelationshipProperties
config
= RelationshipProperties
config { hasNonTrivialInheritanceCycles :: Bool
hasNonTrivialInheritanceCycles = Bool
True }
withCompositionCycles :: RelationshipProperties -> RelationshipProperties
withCompositionCycles :: RelationshipProperties -> RelationshipProperties
withCompositionCycles RelationshipProperties
config
= RelationshipProperties
config { hasCompositionCycles :: Bool
hasCompositionCycles = Bool
True }