never executed always true always false
    1 module Conjure.Language.Attributes where
    2 
    3 import Conjure.Language.Domain (BinaryRelationAttr (..))
    4 import Conjure.Language.Expression.Op.Internal.Common (Lexeme (..))
    5 import Conjure.Prelude
    6 import Data.Map (Map)
    7 import qualified Data.Map.Strict as M
    8 
    9 type Attr = (Lexeme, Bool)
   10 
   11 mapFrom :: [[Attr]] -> Map Lexeme Bool
   12 mapFrom attrs = M.fromList $ concat attrs
   13 
   14 setValidAttrs :: Map Lexeme Bool
   15 setValidAttrs = mapFrom [sizeyAttrs]
   16 
   17 msetValidAttrs :: Map Lexeme Bool
   18 msetValidAttrs = mapFrom [sizeyAttrs, occursAttrs]
   19 
   20 funAttrs :: Map Lexeme Bool
   21 funAttrs = mapFrom [sizeyAttrs, jectivityAttrs, totalityAttrs]
   22 
   23 seqAttrs :: Map Lexeme Bool
   24 seqAttrs = mapFrom [sizeyAttrs, jectivityAttrs]
   25 
   26 relAttrs :: Map Lexeme Bool
   27 relAttrs = mapFrom [sizeyAttrs, binRelAttrs, totalityAttrs]
   28 
   29 partitionAttrs :: Map Lexeme Bool
   30 partitionAttrs = mapFrom [sizeyAttrs, partSizeAttrs,partNumAttrs, regularity]
   31 
   32 sizeyAttrs :: [Attr]
   33 sizeyAttrs =
   34     [ (L_size, True)
   35     , (L_maxSize, True)
   36     , (L_minSize, True)
   37     ]
   38 
   39 occursAttrs :: [Attr]
   40 occursAttrs =
   41     [ (L_minOccur, True)
   42     , (L_maxOccur, True)
   43     ]
   44 
   45 partNumAttrs :: [Attr]
   46 partNumAttrs =
   47     [ (L_numParts, True)
   48     , (L_maxNumParts, True)
   49     , (L_minNumParts, True)
   50     ]
   51 
   52 partSizeAttrs :: [(Lexeme, Bool)]
   53 partSizeAttrs =
   54     [ (L_partSize, True)
   55     , (L_minPartSize, True)
   56     , (L_maxPartSize, True)
   57     ]
   58 
   59 jectivityAttrs :: [(Lexeme, Bool)]
   60 jectivityAttrs =
   61     [ (L_injective, False)
   62     , (L_bijective, False)
   63     , (L_surjective, False)
   64     ]
   65 
   66 binRelAttrs :: [(Lexeme, Bool)]
   67 binRelAttrs =
   68     [ (L_reflexive, False)
   69     , (L_irreflexive, False)
   70     , (L_coreflexive, False)
   71     , (L_symmetric, False)
   72     , (L_antiSymmetric, False)
   73     , (L_aSymmetric, False)
   74     , (L_transitive, False)
   75     , (L_total,False)
   76     , (L_connex, False)
   77     , (L_Euclidean, False)
   78     , (L_serial, False)
   79     , (L_equivalence, False)
   80     , (L_partialOrder, False)
   81     , (L_linearOrder, False)
   82     , (L_weakOrder, False)
   83     , (L_preOrder, False)
   84     , (L_strictPartialOrder, False)
   85     , (L_leftTotal, False)
   86     , (L_rightTotal, False)
   87     ]
   88 
   89 lexemeToBinRel :: Lexeme -> Maybe BinaryRelationAttr
   90 lexemeToBinRel L_reflexive = Just BinRelAttr_Reflexive
   91 lexemeToBinRel L_irreflexive = Just BinRelAttr_Irreflexive
   92 lexemeToBinRel L_coreflexive = Just BinRelAttr_Coreflexive
   93 lexemeToBinRel L_symmetric = Just BinRelAttr_Symmetric
   94 lexemeToBinRel L_antiSymmetric = Just BinRelAttr_AntiSymmetric
   95 lexemeToBinRel L_aSymmetric = Just BinRelAttr_ASymmetric
   96 lexemeToBinRel L_transitive = Just BinRelAttr_Transitive
   97 lexemeToBinRel L_total = Just BinRelAttr_Total
   98 lexemeToBinRel L_connex = Just BinRelAttr_Connex
   99 lexemeToBinRel L_Euclidean = Just BinRelAttr_Euclidean
  100 lexemeToBinRel L_serial = Just BinRelAttr_Serial
  101 lexemeToBinRel L_equivalence = Just BinRelAttr_Equivalence
  102 lexemeToBinRel L_partialOrder = Just BinRelAttr_PartialOrder
  103 lexemeToBinRel L_linearOrder = Just BinRelAttr_LinearOrder
  104 lexemeToBinRel L_weakOrder = Just BinRelAttr_WeakOrder
  105 lexemeToBinRel L_preOrder = Just BinRelAttr_PreOrder
  106 lexemeToBinRel L_strictPartialOrder = Just BinRelAttr_StrictPartialOrder
  107 lexemeToBinRel L_leftTotal = Just BinRelAttr_LeftTotal
  108 lexemeToBinRel L_rightTotal = Just BinRelAttr_RightTotal
  109 lexemeToBinRel _ = Nothing
  110 
  111 totalityAttrs :: [Attr]
  112 totalityAttrs = [(L_total, False)]
  113 
  114 regularity :: [Attr]
  115 regularity = [(L_regular, False)]
  116 
  117 allAttributLexemes :: [Lexeme]
  118 allAttributLexemes =
  119     concatMap
  120         (map fst)
  121         [ sizeyAttrs
  122         , jectivityAttrs
  123         , occursAttrs
  124         , partNumAttrs
  125         , partSizeAttrs
  126         , binRelAttrs
  127         , totalityAttrs
  128         , regularity
  129         ]