never executed always true always false
    1 {-# LANGUAGE DeriveGeneric #-}
    2 {-# LANGUAGE DeriveDataTypeable #-}
    3 {-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
    4 {-# HLINT ignore "Use camelCase" #-}
    5 
    6 module Conjure.Language.Lexemes where
    7 
    8 import Conjure.Prelude
    9 import qualified Data.HashMap.Strict as M
   10 import qualified Data.Text as T
   11 
   12 
   13 
   14 data Lexeme
   15     = LIntLiteral Integer
   16     | LMissingIntLiteral   --helper for missing symbol
   17     | LIdentifier T.Text
   18     | LMissingIdentifier --helper for missing symbol
   19     | LMetaVar T.Text
   20     | LUnexpected T.Text
   21     | LMissingMetaVar --helper for missing symbol
   22     -- general
   23     | L_be
   24     | L_from
   25     | L_of
   26     | L_domain
   27 
   28     | L_language
   29     | L_dim
   30     | L_find
   31     | L_given
   32     | L_letting
   33     | L_where
   34     | L_such
   35     | L_that
   36     | L_minimising
   37     | L_maximising
   38     | L_branching
   39     | L_on
   40     | L_heuristic
   41 
   42     -- type: boolean
   43     | L_bool
   44     | L_false
   45     | L_true
   46 
   47     -- type: integer
   48     | L_int
   49 
   50     -- creating a new type
   51     | L_new
   52     | L_type
   53     | L_enum
   54 
   55     -- type tuple
   56     | L_tuple
   57 
   58     -- type record
   59     | L_record
   60 
   61     -- type variant
   62     | L_variant
   63     | L_active
   64 
   65     -- type: matrix
   66     | L_matrix
   67     | L_indexed
   68     | L_by
   69 
   70     -- type set
   71     | L_set
   72     | L_size
   73     | L_minSize
   74     | L_maxSize
   75 
   76     -- type: mset
   77     | L_mset
   78     | L_minOccur
   79     | L_maxOccur
   80 
   81     -- type: function
   82     | L_function
   83     | L_total
   84     | L_partial
   85     | L_injective
   86     | L_surjective
   87     | L_bijective
   88 
   89     -- type: sequence
   90     | L_sequence
   91 
   92     -- type: relation
   93     | L_relation
   94     | L_reflexive
   95     | L_irreflexive
   96     | L_coreflexive
   97     | L_symmetric
   98     | L_antiSymmetric
   99     | L_aSymmetric
  100     | L_transitive
  101     | L_connex
  102     | L_Euclidean
  103     | L_serial
  104     | L_equivalence
  105     | L_partialOrder
  106     | L_linearOrder
  107     | L_weakOrder
  108     | L_preOrder
  109     | L_strictPartialOrder
  110     | L_leftTotal
  111     | L_rightTotal
  112     -- type: partition
  113     | L_partition
  114     | L_regular
  115     | L_partSize
  116     | L_minPartSize
  117     | L_maxPartSize
  118     | L_numParts
  119     | L_minNumParts
  120     | L_maxNumParts
  121 
  122     -- operators, page 21 of the holy paper
  123     | L_union
  124     | L_intersect
  125     | L_subset
  126     | L_subsetEq
  127     | L_supset
  128     | L_supsetEq
  129     | L_in
  130     | L_max
  131     | L_min
  132     | L_toSet
  133     | L_toMSet
  134     | L_toRelation
  135     | L_defined
  136     | L_range
  137     | L_restrict
  138     | L_image
  139     | L_imageSet
  140     | L_preImage
  141     | L_inverse
  142     | L_together
  143     | L_apart
  144     | L_party
  145     | L_participants
  146     | L_parts
  147     | L_freq
  148     | L_hist
  149 
  150     | L_toInt
  151     | L_makeTable
  152     | L_table
  153 
  154     -- global constraints
  155     | L_allDiff
  156     | L_alldifferent_except
  157     | L_gcc
  158     | L_atleast
  159     | L_atmost
  160 
  161     | L_dontCare
  162 
  163     | L_catchUndef
  164 
  165     -- matrix only operators
  166     | L_flatten
  167     | L_concatenate
  168     | L_normIndices
  169 
  170     -- in the rule language
  171     -- | L_lambda
  172     -- | L_quantifier
  173     -- | L_representation
  174 
  175     -- arithmetic operators
  176 
  177     | L_Plus                --    +           -- sum, infix : (int,int) -> int
  178     | L_Minus               --    -           -- (subtraction, infix : (int,int) -> int) OR (unary minus : int -> int)
  179     | L_Times               --    *           -- multiplication, infix : (int,int) -> int
  180     | L_Div                 --    /           -- integer division, infix
  181     | L_Mod                 --    %           -- modulo, infix
  182     | L_Pow                 --    **          -- exponentiation, infix : (int,int) -> int
  183     | L_factorial
  184 
  185     -- equality
  186 
  187     | L_Eq                  --    =           -- equals, infix.
  188     | L_Neq                 --    !=          -- not-equals, infix
  189 
  190     -- comparison
  191 
  192     | L_Lt                  --    <           -- less-than, infix.
  193     | L_Leq                 --    <=          -- less-than-or-eq, infix.
  194     | L_Gt                  --    >           -- greater-than, infix.
  195     | L_Geq                 --    >=          -- greater-than-or-eq, infix.
  196 
  197     -- logical operators
  198 
  199     | L_And                 --    /\          -- logical-and, infix
  200     | L_Or                  --    \/          -- logical-or, infix.
  201     | L_Imply               --    ->          -- implication, infix
  202     | L_Iff                 --    <->         -- iff, infix.
  203     | L_Not                 --    !           -- negation, prefix
  204     | L_ExclamationMark     -- for poth L_Factorial and L_ExclamationMark
  205 
  206     -- the function arrow
  207 
  208     | L_LongArrow           --    -->         -- function domains and constants
  209 
  210     -- in rule language
  211 
  212     | L_Colon               --    :           -- has-domain, infix, (expr,domain) -> bool. also does pattern matching.
  213     | L_DoubleColon         --    ::          -- has-type, infix, (expr,type) -> bool. also does pattern matching.
  214     | L_At                  --    @           -- bubble operator.
  215 
  216     -- lex operators
  217 
  218     | L_LexGeq              --    >=lex
  219     | L_LexGt               --    >lex
  220     | L_LexLt               --    <=lex
  221     | L_LexLeq              --    <lex
  222 
  223     -- for "abs" and "card"
  224     | L_Bar                 --    |
  225 
  226     -- attaching a type to an expression
  227     | L_BackTick            --    `
  228 
  229     --Quantifiers
  230 
  231     | L_ForAll
  232     | L_Exists
  233     | L_Sum
  234     | L_Product
  235     | L_fXor
  236 
  237     | L_fAnd
  238     | L_fOr
  239 
  240 
  241     -- others
  242     | L_Dot
  243     | L_DoubleDot
  244     | L_Comma
  245     | L_SemiColon
  246 
  247     | L_OpenParen
  248     | L_CloseParen
  249     | L_OpenBracket
  250     | L_CloseBracket
  251     | L_OpenCurly
  252     | L_CloseCurly
  253 
  254     | L_Newline
  255     | L_Carriage
  256     | L_Space
  257     | L_Tab
  258 
  259     | L_SquigglyArrow
  260     | L_CaseSeparator
  261 
  262     | L_HasRepr
  263     | L_HasType
  264     | L_HasDomain
  265     | L_indices
  266 
  267     | L_DotLt
  268     | L_DotLeq
  269     | L_DotGt
  270     | L_DotGeq
  271 
  272     | L_TildeLt
  273     | L_TildeLeq
  274     | L_TildeGt
  275     | L_TildeGeq
  276 
  277     | L_LeftArrow
  278 
  279     | L_subsequence
  280     | L_substring
  281     | L_powerSet
  282 
  283     | L_pred
  284     | L_succ
  285 
  286     -- type functional
  287     | L_transform
  288 
  289     -- helper
  290     | L_Missing MissingStructuralElements
  291     | L_EOF
  292     | L_SpecialCase
  293 
  294     deriving (Eq, Ord, Show,Data,Generic) --Generic
  295 
  296 instance Hashable Lexeme
  297 
  298 data MissingStructuralElements = MissingExpression | MissingDomain | MissingUnknown
  299     deriving (Eq, Ord, Data,Generic) --Generic
  300 instance Show MissingStructuralElements where
  301     show MissingExpression = "Expression"
  302     show MissingDomain = "Domain"
  303     show MissingUnknown = "Unknown"
  304 
  305 instance Hashable MissingStructuralElements
  306 
  307 lexemes :: [(T.Text, Lexeme)]
  308 lexemes = sortBy (flip (comparing (T.length . fst))) $ map swap
  309     [ ( L_be         , "be"         )
  310     , ( L_from       , "from"       )
  311     , ( L_of         , "of"         )
  312     , ( L_domain     , "domain"     )
  313     , ( L_language   , "language"   )
  314     , ( L_dim        , "dim"        )
  315     , ( L_find       , "find"       )
  316     , ( L_given      , "given"      )
  317     , ( L_letting    , "letting"    )
  318     , ( L_where      , "where"      )
  319     , ( L_such       , "such"       )
  320     , ( L_that       , "that"       )
  321     , ( L_minimising , "minimising" )
  322     , ( L_maximising , "maximising" )
  323     , ( L_minimising , "minimizing" )
  324     , ( L_maximising , "maximizing" )
  325     , ( L_branching  , "branching"  )
  326     , ( L_on         , "on"         )
  327     , ( L_heuristic  , "heuristic"  )
  328 
  329     , ( L_bool, "bool" )
  330     , ( L_false, "false" )
  331     , ( L_true, "true" )
  332     , ( L_int, "int" )
  333     , ( L_new, "new" )
  334     , ( L_type, "type" )
  335     , ( L_enum, "enum" )
  336     , ( L_tuple, "tuple" )
  337     , ( L_record, "record" )
  338     , ( L_variant, "variant" )
  339     , ( L_active, "active" )
  340     , ( L_matrix, "matrix" )
  341     , ( L_indexed, "indexed" )
  342     , ( L_by, "by" )
  343     , ( L_set, "set" )
  344     , ( L_size, "size" )
  345     , ( L_minSize, "minSize" )
  346     , ( L_maxSize, "maxSize" )
  347     , ( L_mset, "mset" )
  348     , ( L_minOccur, "minOccur" )
  349     , ( L_maxOccur, "maxOccur" )
  350     , ( L_function, "function" )
  351     , ( L_total, "total" )
  352     , ( L_partial, "partial" )
  353     , ( L_injective, "injective" )
  354     , ( L_surjective, "surjective" )
  355     , ( L_bijective, "bijective" )
  356     , ( L_sequence, "sequence" )
  357     , ( L_relation, "relation")
  358     , ( L_reflexive, "reflexive")
  359     , ( L_irreflexive, "irreflexive")
  360     , ( L_coreflexive, "coreflexive")
  361     , ( L_symmetric, "symmetric")
  362     , ( L_antiSymmetric, "antiSymmetric")
  363     , ( L_aSymmetric, "aSymmetric")
  364     , ( L_transitive, "transitive")
  365     , ( L_connex, "connex")
  366     , ( L_Euclidean, "Euclidean")
  367     , ( L_serial, "serial")
  368     , ( L_equivalence, "equivalence")
  369     , ( L_partialOrder, "partialOrder")
  370     , ( L_linearOrder , "linearOrder")
  371     , ( L_weakOrder , "weakOrder")
  372     , ( L_preOrder , "preOrder")
  373     , ( L_strictPartialOrder , "strictPartialOrder")
  374     , ( L_leftTotal , "leftTotal")
  375     , ( L_rightTotal , "rightTotal")
  376     , ( L_partition, "partition" )
  377     , ( L_regular, "regular" )
  378     , ( L_partSize, "partSize" )
  379     , ( L_minPartSize, "minPartSize" )
  380     , ( L_maxPartSize, "maxPartSize" )
  381     , ( L_numParts, "numParts" )
  382     , ( L_minNumParts, "minNumParts" )
  383     , ( L_maxNumParts, "maxNumParts" )
  384     , ( L_union, "union" )
  385     , ( L_intersect, "intersect" )
  386     , ( L_subset, "subset" )
  387     , ( L_subsetEq, "subsetEq" )
  388     , ( L_supset, "supset" )
  389     , ( L_supsetEq, "supsetEq" )
  390     , ( L_in, "in" )
  391     , ( L_max, "max" )
  392     , ( L_min, "min" )
  393     , ( L_toSet, "toSet" )
  394     , ( L_toMSet, "toMSet" )
  395     , ( L_toRelation, "toRelation" )
  396     , ( L_defined, "defined" )
  397     , ( L_range, "range" )
  398     , ( L_restrict, "restrict" )
  399     , ( L_image, "image" )
  400     , ( L_imageSet, "imageSet" )
  401     , ( L_preImage, "preImage" )
  402     , ( L_inverse, "inverse" )
  403     , ( L_together, "together" )
  404     , ( L_apart, "apart" )
  405     , ( L_party, "party" )
  406     , ( L_participants, "participants" )
  407     , ( L_parts, "parts" )
  408     , ( L_freq, "freq" )
  409     , ( L_hist, "hist" )
  410     , ( L_toInt, "toInt" )
  411     , ( L_makeTable, "makeTable" )
  412     , ( L_table, "table" )
  413 
  414 
  415     , ( L_allDiff, "allDiff" )
  416     , ( L_alldifferent_except, "alldifferent_except" )
  417     , ( L_gcc, "gcc" )
  418     , ( L_atleast, "atleast" )
  419     , ( L_atmost, "atmost" )
  420 
  421     , ( L_dontCare, "dontCare" )
  422     , ( L_catchUndef, "catchUndef" )
  423 
  424     , ( L_flatten, "flatten" )
  425     , ( L_concatenate, "concatenate" )
  426     , ( L_normIndices, "normIndices" )
  427     -- , ( L_lambda, "lambda" )
  428     -- , ( L_quantifier, "quantifier" )
  429     -- , ( L_representation, "representation" )
  430 
  431     , ( L_ForAll            , "forAll"     )
  432     , ( L_Exists           , "exists"     )
  433     , ( L_Sum           , "sum"     )
  434     , ( L_Product           , "product"     )
  435     , ( L_Not           , "not"     )
  436     , ( L_fXor           , "xor"     )
  437     , ( L_fAnd           , "and"     )
  438     , ( L_fOr           , "or"     )
  439 
  440     , ( L_Plus            , "+"     )
  441     , ( L_Minus           , "-"     )
  442     , ( L_Times           , "*"     )
  443     , ( L_Div             , "/"     )
  444     , ( L_Mod             , "%"     )
  445     , ( L_Pow             , "**"    )
  446     , ( L_factorial       , "factorial" )
  447     , ( L_Eq              , "="     )
  448     , ( L_Neq             , "!="    )
  449     , ( L_Lt              , "<"     )
  450     , ( L_Leq             , "<="    )
  451     , ( L_Gt              , ">"     )
  452     , ( L_Geq             , ">="    )
  453     , ( L_And             , "/\\"   )
  454     , ( L_Or              , "\\/"   )
  455     , ( L_Imply           , "->"    )
  456     , ( L_Iff             , "<->"   )
  457     , ( L_ExclamationMark , "!"     )
  458     , ( L_LongArrow       , "-->"   )
  459     , ( L_Colon           , ":"     )
  460     , ( L_DoubleColon     , "::"    )
  461     , ( L_At              , "@"     )
  462     , ( L_LexGeq          , ">=lex" )
  463     , ( L_LexGt           , ">lex"  )
  464     , ( L_LexLeq          , "<=lex" )
  465     , ( L_LexLt           , "<lex"  )
  466     , ( L_Bar             , "|"     )
  467     , ( L_BackTick        , "`"     )
  468     , ( L_Dot             , "."     )
  469     , ( L_DoubleDot       , ".."    )
  470     , ( L_Comma           , ","     )
  471     , ( L_SemiColon       , ";"     )
  472     , ( L_OpenParen       , "("     )
  473     , ( L_CloseParen      , ")"     )
  474     , ( L_OpenBracket     , "["     )
  475     , ( L_CloseBracket    , "]"     )
  476     , ( L_OpenCurly       , "{"     )
  477     , ( L_CloseCurly      , "}"     )
  478 
  479     , ( L_Newline         , "\n"    )
  480     , ( L_Carriage        , "\r"    )
  481     , ( L_Space           , " "     )
  482     , ( L_Tab             , "\t"    )
  483 
  484     , ( L_SquigglyArrow   , "~~>"   )
  485     , ( L_CaseSeparator   , "***"   )
  486 
  487     , ( L_HasRepr         , "hasRepr"   )
  488     , ( L_HasType         , "hasType"   )
  489     , ( L_HasDomain       , "hasDomain" )
  490     , ( L_indices         , "indices"   )
  491 
  492     , ( L_DotLt           , ".<"    )
  493     , ( L_DotLeq          , ".<="   )
  494     , ( L_DotGt           , ".>"    )
  495     , ( L_DotGeq          , ".>="   )
  496 
  497     , ( L_TildeLt         , "~<"    )
  498     , ( L_TildeLeq        , "~<="   )
  499     , ( L_TildeGt         , "~>"    )
  500     , ( L_TildeGeq        , "~>="   )
  501 
  502     , ( L_LeftArrow       , "<-"   )
  503 
  504     , ( L_subsequence     , "subsequence"  )
  505     , ( L_substring       , "substring"    )
  506     , ( L_powerSet        , "powerSet"     )
  507 
  508     , ( L_pred, "pred" )
  509     , ( L_succ, "succ" )
  510 
  511 
  512     , ( L_transform, "transform")
  513 
  514     , ( L_SpecialCase, "?#")
  515     ]
  516 
  517 textToLexeme :: Text -> Maybe Lexeme
  518 textToLexeme t = M.lookup t mapTextToLexeme
  519 
  520 mapTextToLexeme :: M.HashMap T.Text Lexeme
  521 mapTextToLexeme = M.fromList lexemes
  522 
  523 mapLexemeToText :: M.HashMap Lexeme T.Text
  524 mapLexemeToText = M.fromList $ map swap lexemes
  525 
  526 lexemeFace :: Lexeme -> String
  527 lexemeFace L_Newline = "new line"
  528 lexemeFace L_Carriage = "\\r"
  529 lexemeFace L_Space   = "space character"
  530 lexemeFace L_Tab     = "tab character"
  531 lexemeFace (LIntLiteral i) = show i
  532 lexemeFace (LIdentifier i) = T.unpack i
  533 -- lexemeFace (LComment    i) = Pr.text (T.unpack i)
  534 lexemeFace l =
  535     case M.lookup l mapLexemeToText of
  536         Nothing ->  (show l)
  537         Just t  ->  (T.unpack t)
  538 
  539 lexemeFaceDoc :: Lexeme -> Doc
  540 lexemeFaceDoc = stringToDoc . lexemeFace
  541 
  542 lexemeText :: Lexeme -> T.Text
  543 lexemeText (LIdentifier t) =  t
  544 lexemeText l = fromMaybe (T.pack $ show l) (M.lookup l mapLexemeToText)
  545 
  546 --Categories
  547 functionAttributes :: [Lexeme]
  548 functionAttributes = [L_injective,L_size]
  549 
  550 
  551