never executed always true always false
    1 {-# LANGUAGE QuasiQuotes #-}
    2 
    3 module Conjure.Rules.Vertical.MSet.Occurrence where
    4 
    5 import Conjure.Rules.Import
    6 import Conjure.Rules.Definition
    7 
    8 
    9 rule_Comprehension :: Rule
   10 rule_Comprehension = "mset-comprehension{Occurrence}" `Rule` theRule where
   11     theRule z (Comprehension body gensOrConds) = do
   12         (gocBefore, (pat, s), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of
   13             Generator (GenInExpr pat@Single{} s) -> return (pat, s)
   14             _ -> na "rule_Comprehension"
   15         TypeMSet{}             <- typeOf s
   16         MSet_Occurrence        <- representationOf s
   17         [m]                    <- downX1 s
   18         DomainMatrix index _   <- domainOf m
   19         let upd val old = lambdaToFunction pat old val
   20         theyDo <- doDuplicatesMatter z
   21         return
   22             [ RuleResult
   23                 { ruleResultDescr = "Vertical rule for mset-comprehension, Occurrence representation"
   24                 , ruleResultType  = ExpressionRefinement
   25                 , ruleResultHook  = Nothing
   26                 , ruleResult      = do
   27                     (jPat, j) <- quantifiedVar
   28                     let val = j
   29                     let outBody = upd val body
   30                     return $ Comprehension (if theyDo then [essence| &outBody * &m[&j] |]
   31                                                       else outBody)
   32                             $  gocBefore
   33                             ++ [ Generator (GenDomainNoRepr jPat index)
   34                                , Condition [essence| &m[&j] > 0 |]
   35                                ]
   36                             ++ transformBi (upd val) gocAfter
   37                 } ]
   38     theRule _ _ = na "rule_Comprehension"
   39 
   40 
   41 rule_Freq :: Rule
   42 rule_Freq = "mset-freq{Occurrence}" `namedRule` theRule where
   43     theRule p = do
   44         (mset, x)              <- match opFreq p
   45         TypeMSet{}             <- typeOf mset
   46         MSet_Occurrence        <- representationOf mset
   47         [m]                    <- downX1 mset
   48         return
   49             ( "Vertical rule for mset-freq, Occurrence representation"
   50             , return [essence| &m[&x] |]
   51             )