Created
August 16, 2016 03:07
-
-
Save erantapaa/cbf816c28d4b8fe5da93deb4988300ec to your computer and use it in GitHub Desktop.
instances of ... <- return ...
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
| :accelerate-0.15.1.0/Data/Array/Accelerate/Interpreter.hs | |
| 387;14 9: y <- return . fromElt $ ain i | |
| 412;14 9: y <- return . fromElt $ ain (i-1) | |
| 452;14 9: y <- return . fromElt $ ain (n-i) | |
| 475;14 9: y <- return . fromElt $ ain (n-i-1) | |
| 537;18 9: x <- return . fromElt $ ain i | |
| :ACME-0.0.0.1/Acme/Cipher.hs | |
| 105;17 9: (init1, stdgen) <- return (randomLetter stdgen) | |
| 106;17 9: (init2, stdgen) <- return (randomLetter stdgen) | |
| 107;12 9: (init3, _) <- return (randomLetter stdgen) | |
| :acme-year-2015/test/Main.hs | |
| 8;9 9: True <- return (y == fromIntegral currentYear) | |
| :Advgame-0.1.2/Advgame.hs | |
| 214;10 9: haveAll <- return . and =<< mapM haveObject have | |
| 216;10 9: allMisc <- return . and =<< if null misc then return [True] else sequence misc | |
| :AERN-Real-Double-2011.1.0.2/src/Numeric/AERN/RealArithmetic/Basis/Double/FieldOps.hs | |
| 39;11 9: aa <- return $! a | |
| :aeson-schema-0.4.0.0/src/Data/Aeson/Schema/CodeGen.hs | |
| 401;28 9: matchingPatterns <- return (filter (flip PCRE.match (unpack pname) . patternCompiled . fst) $(lift patterns)) | |
| 403;32 9: isAdditionalProperty <- return (null matchingPatterns && pname `notElem` $(lift $ map fst $ HM.toList $ schemaProperties schema)) | |
| :Agda-2.5.1/src/full/Agda/Auto/Typecheck.hs | |
| 468;11 9: sf <- return False {- semiflex hne -} | |
| :Agda-2.5.1/src/full/Agda/Compiler/Epic/Compiler.hs | |
| 197;12 9: emits <- return defs | |
| :Agda-2.5.1/src/full/Agda/Compiler/Epic/FromAgda.hs | |
| 60;12 9: res <- return <$> (etaExpand toEta =<< compileClauses n len ccs) | |
| :Agda-2.5.1/src/full/Agda/Compiler/Epic/Smashing.hs | |
| 125;13 9: retType' <- return retType -- lift $ reduce retType | |
| :Agda-2.5.1/src/full/Agda/Compiler/Epic/Static.hs | |
| 92;13 9: feta <- return term -- etaExpand term | |
| :Agda-2.5.1/src/full/Agda/Compiler/JS/Compiler.hs | |
| 264;5 9: np <- return (arity t - nc) | |
| 293;13 9: (av,bv,es) <- return (mapping (map unArg pats)) | |
| 358;8 9: e <- return (Local (LocalId i)) | |
| :Agda-2.5.1/src/full/Agda/Compiler/JS/Parser.hs | |
| 129;4 9: n <- return (genericLength xs) | |
| 130;5 9: m' <- return (union (fromList (zip xs [n-1,n-2..0])) (M.map (+n) m)) | |
| :Agda-2.5.1/src/full/Agda/Compiler/Treeless/Erase.hs | |
| 200;10 9: mcs <- return $ case I.theDef def of | |
| :Agda-2.5.1/src/full/Agda/Compiler/UHC/Smashing.hs | |
| 147;13 9: retType' <- return retType | |
| :Agda-2.5.1/src/full/Agda/Interaction/BasicOps.hs | |
| 128;15 9: v' <- return $ foldr (\ (Arg ai x) -> I.Lam ai . I.Abs x) v' xs2 | |
| :Agda-2.5.1/src/full/Agda/Interaction/EmacsTop.hs | |
| 70;14 9: _ <- return $! length r -- force to read the full input line | |
| :Agda-2.5.1/src/full/Agda/Interaction/Imports.hs | |
| 516;9 9: -- i <- return $ | |
| 520;9 9: -- i <- return $ | |
| :Agda-2.5.1/src/full/Agda/Syntax/Concrete/Definitions.hs | |
| 778;19 9: d <- return $ FunDef (getRange fits) fits fx ConcreteDef termCheck x cs | |
| :Agda-2.5.1/src/full/Agda/Syntax/Scope/Monad.hs | |
| 415;12 9: y <- return $ setRange rnew y | |
| :Agda-2.5.1/src/full/Agda/Syntax/Translation/InternalToAbstract.hs | |
| 323;17 9: expandAnonDefs <- return expandAnonDefs0 `and2M` displayFormsEnabled | |
| 986;6 9: s <- return $ if isUnderscore s && 0 `freeIn` v then "z" else s | |
| :Agda-2.5.1/src/full/Agda/Termination/TermCheck.hs | |
| 1102;17 9: fs <- return $ map unArg fs | |
| 1219;4 9: v <- return $ ignoreSharing v | |
| :Agda-2.5.1/src/full/Agda/TypeChecking/Conversion.hs | |
| 1102;9 9: as <- return $ [ a | a <- as, not $ a `isStrictlySubsumedBy` bs ] | |
| 1103;9 9: bs <- return $ [ b | b <- bs, not $ b `isStrictlySubsumedBy` as ] | |
| 1107;12 9: -- as <- return $ Set.fromList $ closed0 as | |
| 1108;12 9: -- bs <- return $ Set.fromList $ closed0 bs | |
| 1110;12 9: -- as <- return $ Set.toList $ as Set.\\ cs | |
| 1111;12 9: -- bs <- return $ Set.toList $ bs Set.\\ cs | |
| 1112;9 9: as <- return $ List.sort $ closed0 as | |
| 1113;9 9: bs <- return $ List.sort $ closed0 bs | |
| :Agda-2.5.1/src/full/Agda/TypeChecking/Coverage.hs | |
| 422;6 9: con <- return $ con { conName = c } -- What if we restore the current name? | |
| :Agda-2.5.1/src/full/Agda/TypeChecking/Datatypes.hs | |
| 173;17 9: args <- return $ genericDrop n args | |
| :Agda-2.5.1/src/full/Agda/TypeChecking/MetaVars.hs | |
| 308;12 9: MetaV x _ <- return $ ignoreSharing m -- needs to be strict! | |
| 616;11 9: args <- return $ map (fmap stripDontCare) args | |
| :Agda-2.5.1/src/full/Agda/TypeChecking/Monad/Options.hs | |
| 224;7 9: incs <- return $ if null incs then ["."] else incs | |
| 226;7 9: incs <- return $ map (mkAbsolute . (filePath root </>)) incs | |
| 236;7 9: incs <- return $ incs ++ [primdir] | |
| :Agda-2.5.1/src/full/Agda/TypeChecking/ProjectionLike.hs | |
| 158;13 9: ps <- return $ filter (checkOccurs cls . snd) ps0 | |
| :Agda-2.5.1/src/full/Agda/TypeChecking/Reduce.hs | |
| 591;15 9: es <- return $ es0 ++ es1 | |
| :Agda-2.5.1/src/full/Agda/TypeChecking/Rules/Data.hs | |
| 95;14 9: s <- return $ raise (-nofIxs) s | |
| :Agda-2.5.1/src/full/Agda/TypeChecking/Rules/Def.hs | |
| 182;11 9: cs <- return $ map A.lhsToSpine cs | |
| 557;44 9: (delta1, delta2, perm', t', as, vs) <- return $ | |
| 676;5 9: cs <- return $ map (A.lhsToSpine) cs | |
| 678;5 9: cs <- return $ map (A.spineToLhs) cs | |
| :Agda-2.5.1/src/full/Agda/TypeChecking/Rules/LHS.hs | |
| 718;15 9: gamma' <- return $ mapRelevance updRel <$> gamma' | |
| 793;18 9: delta1' <- return $ mapRelevance ignoreForced <$> delta1' | |
| :Agda-2.5.1/src/full/Agda/TypeChecking/Rules/Term.hs | |
| 334;13 9: info <- return $ mapHiding (mappend h) info | |
| :Agda-2.5.1/src/full/Agda/TypeChecking/Serialise.hs | |
| 156;16 9: (ver, s, _) <- return $ runGetState B.get s 0 | |
| :Agda-2.5.1/src/full/Agda/TypeChecking/SizedTypes/Solve.hs | |
| 234;11 9: -- gamma <- return $ reverse gamma | |
| 237;8 9: -- hs <- return $ sub n hs | |
| :Agda-2.5.1/src/full/Agda/TypeChecking/SizedTypes/WarshallSolver.hs | |
| 898;5 9: cs <- return $ subst sol cs | |
| :Agda-2.5.1/src/full/Agda/TypeChecking/SizedTypes.hs | |
| 557;7 9: cs <- return $ mapMaybe oldCanonicalizeSizeConstraint cs | |
| :ajhc-0.8.0.10/src/C/FromGrin2.hs | |
| 563;18 9: [arg] <- return as | |
| 897;22 9: c <- return $ chr c | |
| :ajhc-0.8.0.10/src/DataConstructors.hs | |
| 348;56 9: (ELit LitCons { litName = n, litArgs = []}) <- return $ followAliases dataTable st | |
| 367;56 9: (ELit LitCons { litName = n, litArgs = []}) <- return $ followAliases dataTable st | |
| 536;26 9:nameToOpTy n = do RawType <- return $ nameType n; Op.readTy (show n) | |
| 682;49 9: ELit LitCons { litName = n } <- return $ followAliases fullDataTable te | |
| :ajhc-0.8.0.10/src/DerivingDrift/Drift.hs | |
| 28;11 9: xs <- return $ map (derive isEnum d) derives | |
| 32;13 9:-- xs <- return $ map (derive False d) derives | |
| :ajhc-0.8.0.10/src/E/CPR.hs | |
| 121;19 9: (e',v) <- return $ cprAnalyze' env e | |
| :ajhc-0.8.0.10/src/E/E.hs | |
| 111;32 9: (TypeConstructor,(mod',an)) <- return $ fromName n | |
| :ajhc-0.8.0.10/src/E/LambdaLift.hs | |
| 175;21 9: (n,as,v) <- return $ combTriple comb | |
| 268;21 9: --(e,tn) <- return $ etaReduce e | |
| 278;25 9: --(e,tn) <- return $ etaReduce e | |
| :ajhc-0.8.0.10/src/E/Main.hs | |
| 135;7 9: ds <- return $ ds ++ nds | |
| 150;9 9: prog <- return prog { progSeasoning = seasoning } | |
| 151;18 9: Identity prog <- return $ programMapDs (\ (t,e) -> return (shouldBeExported (getExports $ hoTcInfo ho') t,e)) $ atomizeApps False (programSetDs ds prog) | |
| 157;9 9: prog <- return $ progCombinators_u (map addRule) prog | |
| 158;8 9: cho <- return $ updateChoHo $ choCombinators_u (fmap addRule) cho | |
| 161;9 9: prog <- return $ runIdentity $ annotateProgram (choVarMap cho) (idann theProps) letann lamann prog | |
| 167;9 9: prog <- return $ prog { progEntry = entryPoints `mappend` progSeasoning prog } | |
| 274;14 9: mprog <- return $ E.CPR.cprAnalyzeProgram mprog | |
| 278;14 9: mprog <- return mprog' | |
| 284;16 9: --mprog <- return $ E.CPR.cprAnalyzeProgram mprog | |
| 289;14 9: mprog <- return $ etaAnnotateProgram mprog | |
| 291;14 9: mprog <- return $ E.CPR.cprAnalyzeProgram mprog | |
| 409;9 9: prog <- return $ programUpdate prog { | |
| 438;12 9: es' <- return [ combBody_u floatInward e | e <- es' ] | |
| 456;13 9: prog <- return $ atomizeApps True prog | |
| 471;9 9: prog <- return $ runIdentity $ annotateProgram mempty (\_ nfo -> return $ | |
| 495;9 9: prog <- return $ E.CPR.cprAnalyzeProgram prog | |
| 502;9 9: prog <- return $ runIdentity $ programMapBodies (return . cleanupE) prog | |
| 529;9 9: prog <- return $ E.CPR.cprAnalyzeProgram prog | |
| 538;9 9: prog <- return $ atomizeApps True prog | |
| 550;10 9: e <- return $ runReader (g e) Set.empty | |
| 551;11 9: tt <- return $ runReader (boxify (tvrType t)) Set.empty | |
| :ajhc-0.8.0.10/src/E/PrimDecode.hs | |
| 140;25 9: Just ret <- return $ boxResult dataTable rType $ \tr str -> | |
| 145;25 9: Just res <- return $ boxResult dataTable rType $ \tr str -> | |
| 149;25 9: Just res <- return $ boxResult dataTable rType $ \tr str -> | |
| 171;17 9: Just ret <- return $ boxResult dataTable rType $ \tr str -> | |
| 186;17 9: Just res <- return $ boxResult dataTable rType $ \tr str -> | |
| 192;17 9: Just res <- return $ boxResult dataTable rType $ \tr str -> | |
| :ajhc-0.8.0.10/src/E/Show.hs | |
| 96;7 9: s <- return $ fromMaybe s (shortenName s) | |
| 101;7 9: s <- return $ fromMaybe s (shortenName s) | |
| :ajhc-0.8.0.10/src/E/SSimplify.hs | |
| 594;31 9: varval = do EVar v <- return e; mlookup (tvrIdent v) (envInScope inb) | |
| 708;27 9: b' <- return b' { tvrIdent = nn } | |
| :ajhc-0.8.0.10/src/E/Traverse.hs | |
| 58;84 9: z ELetRec { eDefs = aa, eBody = ab } = do aa <- mapM (\x -> do x <- (do (aa,ab) <- return x; aa <- mapmTvr g aa;ab <- f ab;return (aa,ab)); return x) aa;ab <- f ab; return $ ELetRec aa ab | |
| :ajhc-0.8.0.10/src/E/TypeAnalysis.hs | |
| 325;18 9: False <- return $ isUnused env t | |
| 326;20 9: Just nt <- return $ Info.lookup (tvrInfo t) | |
| 327;20 9: Just tt <- return $ getTyp (getType t) dataTable nt | |
| 358;7 9: ds <- return $ map combBind ds | |
| :ajhc-0.8.0.10/src/E/TypeCheck.hs | |
| 197;21 9: ESort s1 <- return $ getType a | |
| 198;21 9: ESort s2 <- return $ getType b | |
| :ajhc-0.8.0.10/src/FrontEnd/Exports.hs | |
| 110;20 9: Just as <- return $ hsImportDeclAs x `mplus` Just (hsImportDeclModule x) | |
| :ajhc-0.8.0.10/src/FrontEnd/ParseUtils.hs | |
| 393;23 9: (n:ns) <- return $ reverse names | |
| 400;21 9: conv <- return (if conv == CApi then CCall else conv) | |
| :ajhc-0.8.0.10/src/FrontEnd/Tc/Main.hs | |
| 684;16 9: rs1 <- return $ simplify ch rs1 | |
| 685;16 9: rs2 <- return $ simplify ch rs2 | |
| :ajhc-0.8.0.10/src/FrontEnd/Tc/Module.hs | |
| 266;16 9: localVarEnv <- return $ localVarEnv `Map.union` noDefaultSigs | |
| :ajhc-0.8.0.10/src/Grin/Devolve.hs | |
| 101;15 9: ne <- return (:>>=) `ap` twiddle x `ap` twiddle lam | |
| 114;15 9: ne <- return (App a) `ap` mapM twiddleVal vs `ap` return t | |
| :ajhc-0.8.0.10/src/Grin/FromE.hs | |
| 106;16 9: RawType <- return $ nameType n | |
| 183;7 9: ds <- return $ flattenScc $ stronglyConnComp [ (a,x, concatMap tf (freeVars z)) | a@(x,(_ :-> z)) <- ds] | |
| 195;8 9: efv <- return [] | |
| 382;11 9: as <- return $ args as | |
| 603;11 9: as <- return $ args as | |
| 619;23 9: as <- return $ keepIts as | |
| :ajhc-0.8.0.10/src/Grin/Lint.hs | |
| 262;19 9: [NodeC {}] <- return vs | |
| 279;17 9: NodeC {} <- return v | |
| :ajhc-0.8.0.10/src/Grin/Main.hs | |
| 76;6 9: x <- return $ twiddleGrin x | |
| 77;8 9: -- x <- return $ normalizeGrin x | |
| 78;8 9:-- x <- return $ twiddleGrin x | |
| :ajhc-0.8.0.10/src/Ho/Binary.hs | |
| 30;9 9: True <- return $ ct == cff_magic | |
| :ajhc-0.8.0.10/src/Ho/Build.hs | |
| 475;11 9: Just x <- return $ Map.lookup root mmap | |
| :ajhc-0.8.0.10/src/Ho/Library.hs | |
| 137;26 9: (x:_) <- return $ filter isGood xs | |
| 141;23 9: [] <- return $ versionBranch vrs | |
| :ajhc-0.8.0.10/src/Interactive.hs | |
| 179;12 9: stmt''' <- return $ FrontEnd.Infix.infixStatement (hoFixities hoE) stmt'' | |
| :ajhc-0.8.0.10/src/Options.hs | |
| 364;6 9: o <- return (foldl (flip ($)) emptyOpt o) | |
| :ajhc-0.8.0.10/src/Util/SHA1.hs | |
| 81;8 9: len <- return $ fromIntegral len | |
| :alpha-1.0.15/src/Alpha.hs | |
| 93;7 9: skip <- return (not force) <&&> fileExist langFile <&&> maybe (return True) (langFile `newerThan`) source | |
| :applicative-fail-1.1.1/src/Control/Monad/Fail.hs | |
| 46;21 9,37 9:>>> runFailT $ do {a <- return 10; b <- return 20; return (a, b)} | |
| 61;66 9:>>> fmap runDLFail $ runFailT $ do {a <- mwarn 10 *> return 15; b <- return 20; return (a, b)} | |
| :apply-refact-0.2.0.0/src/Refact/Apply.hs | |
| 82;14 9: (ares, res) <- return . flip evalState 0 $ | |
| :apply-refact-0.2.0.0/tests/examples/Extensions9.hs | |
| 2;18 9:main = do {rec {x <- return 1}; print x} | |
| :apply-refact-0.2.0.0/tests/examples/Extensions9.hs.expected | |
| 2;18 9:main = do {rec {x <- return 1}; print x} | |
| :apply-refact-0.2.0.0/tests/examples/Monad10.hs | |
| 1;11 9:yes = do x <- return y; foo x | |
| :apply-refact-0.2.0.0/tests/examples/Monad10.hs.refact | |
| 1;67 9:[("tests/examples/Monad10.hs:1:7: Warning: Use let\nFound:\n do x <- return y\n foo x\nWhy not:\n do let x = y\n foo x\n",[Replace {rtype = Stmt, pos = SrcSpan {startLine = 1, startCol = 10, endLine = 1, endCol = 23}, subts = [("lhs",SrcSpan {startLine = 1, startCol = 10, endLine = 1, endCol = 11}),("rhs",SrcSpan {startLine = 1, startCol = 22, endLine = 1, endCol = 23})], orig = "let lhs = rhs"}])] | |
| :apply-refact-0.2.0.0/tests/examples/Monad11.hs | |
| 1;11 9:yes = do x <- return $ y + z; foo x | |
| :apply-refact-0.2.0.0/tests/examples/Monad11.hs.refact | |
| 1;67 9:[("tests/examples/Monad11.hs:1:7: Warning: Use let\nFound:\n do x <- return $ y + z\n foo x\nWhy not:\n do let x = y + z\n foo x\n",[Replace {rtype = Stmt, pos = SrcSpan {startLine = 1, startCol = 10, endLine = 1, endCol = 29}, subts = [("lhs",SrcSpan {startLine = 1, startCol = 10, endLine = 1, endCol = 11}),("rhs",SrcSpan {startLine = 1, startCol = 24, endLine = 1, endCol = 29})], orig = "let lhs = rhs"}])] | |
| :apply-refact-0.2.0.0/tests/examples/Monad12.hs | |
| 1;10 9:no = do x <- return x; foo x | |
| :apply-refact-0.2.0.0/tests/examples/Monad12.hs.expected | |
| 1;10 9:no = do x <- return x; foo x | |
| :apply-refact-0.2.0.0/tests/examples/Monad13.hs | |
| 1;10 9,25 9:no = do x <- return y; x <- return y; foo x | |
| :apply-refact-0.2.0.0/tests/examples/Monad13.hs.expected | |
| 1;10 9,25 9:no = do x <- return y; x <- return y; foo x | |
| :asn1-encoding-0.9.3/tests/Tests.hs | |
| 108;13 9: nsec <- return 0 | |
| :bake-0.4/src/Development/Bake/Core/GC.hs | |
| 31;10 9: bytes <- return $ max (floor $ fromIntegral total * ratio) bytes | |
| :bake-0.4/src/Development/Bake/Server/Memory.hs | |
| 82;13 9: messages <- return $ concat [(a,b) : map (,b) (admins mem) | (a,b) <- messages] | |
| :bake-0.4/src/Development/Bake/Server/Start.hs | |
| 143;8 9: mem <- return mem{admins = admins ,fatal = ["Failed to initialise, " ++ TL.unpack (aStdout answer) | isNothing res]} | |
| :bake-0.4/src/Development/Bake/Test/Simulate.hs | |
| 82;8 9: mem <- return mem | |
| 93;10 9: s <- return s{user = u} | |
| 94;16 9: (msg,s) <- return $ case res of | |
| 105;10 9: q <- return $ either error id <$> q | |
| 108;10 9: s <- return s{memory = mem} | |
| 109;10 9: s <- return $ case q of | |
| :base-4.9.0.0/Data/Complex.hs | |
| 217;26 9: q <- return $ castPtr p | |
| 222;26 8: q <-return $ (castPtr p) | |
| :base-4.9.0.0/Foreign/Storable.hs | |
| 221;26 9: q <- return $ castPtr p | |
| 226;26 8: q <-return $ (castPtr p) | |
| :base-4.9.0.0/GHC/IO/Encoding/CodePage/API.hs | |
| 71;10 9: ptr <- return $ castPtr ptr | |
| 73;10 9: ptr <- return $ castPtr $ advancePtr ptr 1 | |
| 78;10 9: ptr <- return $ castPtr ptr | |
| 80;10 9: ptr <- return $ castPtr $ advancePtr ptr 1 | |
| :base-4.9.0.0/GHC/IO/Handle/FD.hs | |
| 222;7 9: fd <- return fd0 | |
| :base-orphans-0.5.4/src/Data/Orphans.hs | |
| 377;26 9: q <- return $ castPtr p | |
| 382;26 8: q <-return $ (castPtr p) | |
| 390;26 9: q <- return $ castPtr p | |
| 395;26 8: q <-return $ (castPtr p) | |
| :bein-0.3.3/Bein/Web/Commands/Local.hs | |
| 177;7 9: pr <- return (maybeFromSql rProgram) |>>=| getObject | |
| :bibdb-0.4.2/dist/build/bibdb/bibdb-tmp/Parser/Lexer.hs | |
| 430;7 9: span <- return makeSrcSpanLengthEnd `ap` getSrcLoc `ap` return (fromIntegral len) | |
| :bighugethesaurus-0.1.0.0/src/Text/Thesaurus.hs | |
| 20;29 9: [pos',relation',related] <- return $ splitOn "|" word | |
| :binary-0.8.3.0/benchmarks/GenericsBenchCache.hs | |
| 34;44 9: , Just (pkg, version) <- return (readFilePath path) ] | |
| 38;43 9: , ParseOk _warns gpd <- return (parsePackageDescription (LC8.unpack content)) ] | |
| :bindings-DSL-1.0.23/Bindings/Utilities.hs | |
| 32;3 9: u <- return undefined | |
| :bio-0.5.3/Bio/Alignment/ACE.hs | |
| 206;11 9: (s,gaps) <- return . extractGaps =<< sdata | |
| :bio-0.5.3/Bio/GFF3/Test.hs | |
| 54;25 9: score <- return Nothing -- Tricky to ask strict equality in a Double | |
| :bioace-0.0.1/src/Bio/Alignment/Ace.hs | |
| 210;11 9: (s,gaps) <- return . (\x -> extractGaps $ SeqData {unSD = x}) =<< sdata | |
| :Biobase-0.3.1.1/Biobase/DataSource/Mafft/Import.hs | |
| 30;6 9: res <- return $ runP pFile () fname content | |
| :biohazard-0.6.5/tools/redeye-dar.hs | |
| 205;21 9: [Library _ fs _] <- return . filter ((fromString lname ==) . library_name) . concatMap sample_libraries . M.elems | |
| :bird-0.0.19/bin/bird.hs | |
| 19;20 9: appModuleName <- return $ head . reverse $ split '/' appModuleNamePath | |
| 30;20 9: appModuleName <- return $ head . reverse $ split '/' appModuleNamePath | |
| 35;20 9: appModuleName <- return $ head . reverse $ split '/' appModuleNamePath | |
| :bitspeak-0.0.3/src/Gui.hs | |
| 92;17 9: dataToWindow <- return $ do | |
| 103;14 9: keyAction <- return $ \k -> do | |
| 123;17 9: callback <- return $ \_ _ key _ -> keyAction key >> return c'TRUE | |
| :bitspeak-0.0.3/src/Main.hs | |
| 42;17 9: resetSufixes <- return $ readIORef currentWord >>= \w -> readIORef corpus >>= | |
| 46;17 9: resetChoices <- return $ readIORef sufixes >>= \s -> | |
| 49;14 9: addToWord <- return $ \c -> modifyIORef currentWord (++ [c]) | |
| 51;14 9: enterWord <- return $ readIORef currentWord >>= \w -> when (not $ null w) $ | |
| 54;13 9: undoWord <- return $ do | |
| :blakesum-demo-0.5/Main.hs | |
| 129;13 9: hash <- return $ getHash salt message | |
| :blank-canvas-0.6/wiki-suite/Global_Composite_Operations.hs | |
| 15;14 9: (w,h) <- return (round (width context :: Double) :: Int, | |
| :blip-0.2.1/src/Compile.hs | |
| 125;20 9: canonicalPath <- return path | |
| :Bookshelf-0.6/Generate.hs | |
| 135;14 9: Just name <- return $ mainDocument shelfInfo | |
| 200;41 9: [Plain [Str f'], BulletList bulls] <- return bs | |
| :bytestring-handle-0.1.0.4/src/Data/ByteString/Handle/Read.hs | |
| 197;14 9: localeEnc <- return localeEncoding | |
| :bytestring-handle-0.1.0.4/src/Data/ByteString/Handle/Write.hs | |
| 168;14 9: localeEnc <- return localeEncoding | |
| :cabal-helper-0.7.1.0/CabalHelper/Compile.hs | |
| 275;13 9: cabal_opts <- return $ concat | |
| :cabal-install-1.24.0.0/Distribution/Client/FileMonitor.hs | |
| 699;16 9: matches <- return . filter (matchGlob glob) | |
| :cabal-install-1.24.0.0/Distribution/Client/Init.hs | |
| 181;11 13: pkgName' <- return (flagToMaybe $ packageName flags) | |
| 206;5 13: v' <- return (flagToMaybe $ version flags) | |
| 214;6 13: lic <- return (flagToMaybe $ license flags) | |
| 230;15 13: authorName' <- return (flagToMaybe $ author flags) | |
| 234;15 13: authorEmail' <- return (flagToMaybe $ email flags) | |
| 246;6 13: hp' <- return (flagToMaybe $ homepage flags) | |
| 260;6 13: syn <- return (flagToMaybe $ synopsis flags) | |
| 270;6 13: cat <- return (flagToMaybe $ category flags) | |
| 278;16 13: extraSrcFiles <- return (extraSrc flags) | |
| 309;8 13: isLib <- return (flagToMaybe $ packageType flags) | |
| 341;7 13: lang <- return (flagToMaybe $ language flags) | |
| 354;14 13: genComments <- return (not <$> flagToMaybe (noComments flags)) | |
| 364;10 9: srcDirs <- return (sourceDirs flags) | |
| 391;12 14: Just mods <- return (exposedModules flags) | |
| 394;8 13: tools <- return (buildTools flags) | |
| 397;7 14: deps <- return (dependencies flags) | |
| 409;7 13: exts <- return (otherExts flags) | |
| :cabal-install-bundle-1.18.0.2.1/Control/Monad/State/Lazy.hs | |
| 100;36 9:-- > (newTable, newPos) <- return (nNode x table) | |
| :cabal-install-bundle-1.18.0.2.1/Control/Monad/State/Strict.hs | |
| 100;36 9:-- > (newTable, newPos) <- return (nNode x table) | |
| :cabal-install-bundle-1.18.0.2.1/Control/Monad/Trans/State/Lazy.hs | |
| 336;33 9:> (newTable, newPos) <- return (nNode x table) | |
| :cabal-install-bundle-1.18.0.2.1/Control/Monad/Trans/State/Strict.hs | |
| 336;33 9:> (newTable, newPos) <- return (nNode x table) | |
| :cabal-install-bundle-1.18.0.2.1/Distribution/Client/Init.hs | |
| 156;11 13: pkgName' <- return (flagToMaybe $ packageName flags) | |
| 167;5 13: v' <- return (flagToMaybe $ version flags) | |
| 175;6 13: lic <- return (flagToMaybe $ license flags) | |
| 191;15 13: authorName' <- return (flagToMaybe $ author flags) | |
| 195;15 13: authorEmail' <- return (flagToMaybe $ email flags) | |
| 207;6 13: hp' <- return (flagToMaybe $ homepage flags) | |
| 221;6 13: syn <- return (flagToMaybe $ synopsis flags) | |
| 231;6 13: cat <- return (flagToMaybe $ category flags) | |
| 239;16 13: extraSrcFiles <- return (extraSrc flags) | |
| 263;8 13: isLib <- return (flagToMaybe $ packageType flags) | |
| 275;7 13: lang <- return (flagToMaybe $ language flags) | |
| 288;14 13: genComments <- return (not <$> flagToMaybe (noComments flags)) | |
| 298;10 13: srcDirs <- return (sourceDirs flags) | |
| 322;12 14: Just mods <- return (exposedModules flags) | |
| 325;8 13: tools <- return (buildTools flags) | |
| 328;7 14: deps <- return (dependencies flags) | |
| 340;7 13: exts <- return (otherExts flags) | |
| :cabal-install-bundle-1.18.0.2.1/Distribution/Client/SrcDist.hs | |
| 44;6 9: pkg <- return . flattenPackageDescription | |
| :cabal-install-ghc72-0.10.4/Distribution/Client/Init.hs | |
| 121;11 13: pkgName' <- return (flagToMaybe $ packageName flags) | |
| 132;5 13: v' <- return (flagToMaybe $ version flags) | |
| 140;6 13: lic <- return (flagToMaybe $ license flags) | |
| 152;15 13: authorName' <- return (flagToMaybe $ author flags) | |
| 156;15 13: authorEmail' <- return (flagToMaybe $ email flags) | |
| 168;6 13: hp' <- return (flagToMaybe $ homepage flags) | |
| 182;6 13: syn <- return (flagToMaybe $ synopsis flags) | |
| 192;6 13: cat <- return (flagToMaybe $ category flags) | |
| 200;8 13: isLib <- return (flagToMaybe $ packageType flags) | |
| 212;10 13: srcDirs <- return (sourceDirs flags) | |
| 231;7 14: mods <- return (exposedModules flags) | |
| 234;8 13: tools <- return (buildTools flags) | |
| :cabal-install-ghc72-0.10.4/Distribution/Client/Install.hs | |
| 757;18 9: testsResult <- return TestsNotTried --TODO: add optional tests | |
| :cabal-install-ghc72-0.10.4/Distribution/Client/SrcDist.hs | |
| 38;6 9: pkg <- return . flattenPackageDescription | |
| :cabal-install-ghc74-0.10.4/Distribution/Client/Init.hs | |
| 121;11 13: pkgName' <- return (flagToMaybe $ packageName flags) | |
| 132;5 13: v' <- return (flagToMaybe $ version flags) | |
| 140;6 13: lic <- return (flagToMaybe $ license flags) | |
| 152;15 13: authorName' <- return (flagToMaybe $ author flags) | |
| 156;15 13: authorEmail' <- return (flagToMaybe $ email flags) | |
| 168;6 13: hp' <- return (flagToMaybe $ homepage flags) | |
| 182;6 13: syn <- return (flagToMaybe $ synopsis flags) | |
| 192;6 13: cat <- return (flagToMaybe $ category flags) | |
| 200;8 13: isLib <- return (flagToMaybe $ packageType flags) | |
| 212;10 13: srcDirs <- return (sourceDirs flags) | |
| 231;7 14: mods <- return (exposedModules flags) | |
| 234;8 13: tools <- return (buildTools flags) | |
| :cabal-install-ghc74-0.10.4/Distribution/Client/Install.hs | |
| 757;18 9: testsResult <- return TestsNotTried --TODO: add optional tests | |
| :cabal-install-ghc74-0.10.4/Distribution/Client/Install.hs~ | |
| 757;18 9: testsResult <- return TestsNotTried --TODO: add optional tests | |
| :cabal-install-ghc74-0.10.4/Distribution/Client/SrcDist.hs | |
| 38;6 9: pkg <- return . flattenPackageDescription | |
| :cabal-progdeps-1.0/progdeps.hs | |
| 44;17 9: curdir <- return . head . (++) args . flip (:) [] =<< getCurrentDirectory | |
| :cabal-src-0.3.0.1/cabal-src-install.hs | |
| 72;18 9: Right tarPath <- return $ TE.toTarPath False $ concat | |
| :cabalvchk-0.3/ghcpkgchk.hs | |
| 47;9 9: pkgInf <- return . lookupPackageName pkgIdx $ PackageName p | |
| 68;18 9: res <- return $ vchk ipvs vrange | |
| :caffegraph-0.1.0.2/NN/Examples/GoogLeNet.hs | |
| 85;22 9: (_, representation) <- return (incepted, incepted) >- sequential [topPool, dropout 0.4, topFc] | |
| :cake3-0.6.0/src/Development/Cake3/Ext/UrWeb.hs | |
| 454;17 9: (e,urls) <- return $ runWriter $ parse_css src_contents' $ \x -> do | |
| :caledon-3.2.1.0/HOU.hs | |
| 748;5 9: ty <- return $ alphaConvert mempty mempty ty | |
| 749;6 9: val <- return $ alphaConvert mempty mempty val | |
| :camfort-0.700/Analysis/Syntax.hs | |
| 225;34 9: ss <- return $ successorsRoot f | |
| :camfort-0.700/Analysis/Types.hs | |
| 46;26 9: tenv' <- return $ gtypes x | |
| :camfort-0.700/Main.hs | |
| 328;27 9: ds' <- return $ ds \\ [".", ".."] -- remove '.' and '..' entries | |
| :camfort-0.700/Output.hs | |
| 326;43 9: (_, inp') <- return $ takeBounds (cursor, cursor') inp | |
| 330;43 9: (_, inp'') <- return $ takeBounds (cursor', cursor'') inp' | |
| :caramia-0.7.2.2/src/Graphics/Caramia/Render.hs | |
| 497;11 9: pr <- return . boundPrimitiveRestart =<< get | |
| :carray-0.1.6.4/tests/meteor-contest-c.hs | |
| 282;6 9: n <- return.read.head =<< getArgs | |
| :carray-0.1.6.4/tests/meteor-contest-u.hs | |
| 281;6 9: n <- return.read.head =<< getArgs | |
| :cassandra-thrift-0.8.5.1/Database/Cassandra/Thrift/Cassandra.hs | |
| 2633;5 9: rs <- return (Login_result Nothing Nothing) | |
| 2650;5 9: rs <- return (Set_keyspace_result Nothing) | |
| 2664;5 9: rs <- return (Get_result Nothing Nothing Nothing Nothing Nothing) | |
| 2687;5 9: rs <- return (Get_slice_result Nothing Nothing Nothing Nothing) | |
| 2707;5 9: rs <- return (Get_count_result Nothing Nothing Nothing Nothing) | |
| 2727;5 9: rs <- return (Multiget_slice_result Nothing Nothing Nothing Nothing) | |
| 2747;5 9: rs <- return (Multiget_count_result Nothing Nothing Nothing Nothing) | |
| 2767;5 9: rs <- return (Get_range_slices_result Nothing Nothing Nothing Nothing) | |
| 2787;5 9: rs <- return (Get_indexed_slices_result Nothing Nothing Nothing Nothing) | |
| 2807;5 9: rs <- return (Insert_result Nothing Nothing Nothing) | |
| 2827;5 9: rs <- return (Add_result Nothing Nothing Nothing) | |
| 2847;5 9: rs <- return (Remove_result Nothing Nothing Nothing) | |
| 2867;5 9: rs <- return (Remove_counter_result Nothing Nothing Nothing) | |
| 2887;5 9: rs <- return (Batch_mutate_result Nothing Nothing Nothing) | |
| 2907;5 9: rs <- return (Truncate_result Nothing Nothing) | |
| 2924;5 9: rs <- return (Describe_schema_versions_result Nothing Nothing) | |
| 2938;5 9: rs <- return (Describe_keyspaces_result Nothing Nothing) | |
| 2952;5 9: rs <- return (Describe_cluster_name_result Nothing) | |
| 2963;5 9: rs <- return (Describe_version_result Nothing) | |
| 2974;5 9: rs <- return (Describe_ring_result Nothing Nothing) | |
| 2988;5 9: rs <- return (Describe_partitioner_result Nothing) | |
| 2999;5 9: rs <- return (Describe_snitch_result Nothing) | |
| 3010;5 9: rs <- return (Describe_keyspace_result Nothing Nothing Nothing) | |
| 3027;5 9: rs <- return (Describe_splits_result Nothing Nothing) | |
| 3041;5 9: rs <- return (System_add_column_family_result Nothing Nothing Nothing) | |
| 3058;5 9: rs <- return (System_drop_column_family_result Nothing Nothing Nothing) | |
| 3075;5 9: rs <- return (System_add_keyspace_result Nothing Nothing Nothing) | |
| 3092;5 9: rs <- return (System_drop_keyspace_result Nothing Nothing Nothing) | |
| 3109;5 9: rs <- return (System_update_keyspace_result Nothing Nothing Nothing) | |
| 3126;5 9: rs <- return (System_update_column_family_result Nothing Nothing Nothing) | |
| 3143;5 9: rs <- return (Execute_cql_query_result Nothing Nothing Nothing Nothing Nothing) | |
| :casui-0.3/Casui/Compile.hs | |
| 22;8 9: ctx <- return . Context [] . ModuleList . (mlist ++) =<< listBuiltinModules | |
| :Catana-0.3/Control/Monad/Catana.hs | |
| 110;11 9:> rec fib <- return $ \x -> | |
| :chalkboard-1.9.0.16/Graphics/ChalkBoard/OpenGL/CBBE.hs | |
| 301;19 9: imgNum <- return $ hashUnique imgUnique | |
| :chaselev-deque-0.5.0.5/RegressionTests/Issue5B.hs | |
| 292;6 9: b <- return (b - 1) -- shadowing | |
| :chatty-text-0.6.2.1/Text/Chatty/Typograph.hs | |
| 105;15 9: tx <- return () | |
| :chp-2.2.0.1/Control/Concurrent/CHP/Channels/Communication.hs | |
| 39;33 11:-- > x <- return y | |
| 48;33 11:-- > x <- return y | |
| :chp-2.2.0.1/Control/Concurrent/CHP/Channels.hs | |
| 58;40 16:-- > x <- return y | |
| :cio-0.1.0/src/CIO.hs | |
| 101;15 9: (as, ws) <- return . unzip =<< sequenceConcurrently cioActions | |
| 106;15 9: (as, ws) <- return . unzip =<< sequenceConcurrently' cioActions | |
| :CLASE-2009.2.11/Data/Cursor/CLASE/Persistence.hs | |
| 122;33 9: (locFrom :: TypeRep l from') <- return (reify (undefined :: from')) | |
| :clustertools-0.1.5/src/Formats.hs | |
| 25;9 9: (h:ls) <- return . map words . lines =<< readFile f | |
| :clustertools-0.1.5/src/Xcerpt.lhs | |
| 22;13 9: (opts,args) <- return . partition (\a->not (null a) && head a=='-') =<< getArgs | |
| 27;10 9: d <- return . mkdict =<< dict | |
| :codo-notation-0.5.2/src/Language/Haskell/Codo.lhs | |
| 50;27 9:> s'' <- return ((take (snd (loc_start loc) - 1) (repeat ' ')) ++ s) | |
| 91;32 9:> col <- return $ sourceColumn pos | |
| 92;35 9:> marker <- return $ ("_reserved_codo_block_marker_\n" ++ (take (col - 1) (repeat ' '))) | |
| :com-1.2.3.1/System/Win32/Com/Automation/TypeLib.hs | |
| 165;8 9: tag <- return (read_tag) | |
| 245;13 9: rgbounds <- return pf3 | |
| 1025;8 9: tag <- return (read_tag) | |
| :Combinatorrent-0.3.2/src/Process/Peer.hs | |
| 293;35 9: u <- return $ RC.update up $ upRate s | |
| :Combinatorrent-0.3.2/src/Protocol/BCode.hs | |
| 255;24 9: v6 <- return $ maybe (B.empty) id $ searchStr "peers6" bc | |
| :compact-map-2008.11.9/src/Data/CompactMap/Index.hs | |
| 356;27 9: = do eIdx <- return idx -- getElement idx -- set =<< extractElemIdx ptr idx | |
| 373;27 9: = do eIdx <- return idx -- getElement idx -- set =<< extractElemIdx ptr idx | |
| :competition-0.2.0.0/Code/Competition.hs | |
| 38;10 9: inputFn <- return $ head args | |
| 50;10 9: answers <- return $ map solve problems | |
| 51;9 9: output <- return $ (unlines . caseify) answers | |
| :compilation-0.0.0.3/Control/Compilation/Environment.hs | |
| 43;34 9: env :: StateExtensionEnv b <- return $ project s | |
| 49;34 9: env :: StateExtensionEnv b <- return $ project s | |
| 55;34 9: env :: StateExtensionEnv b <- return $ project s | |
| 61;34 9: env :: StateExtensionEnv b <- return $ project s | |
| 72;34 9: env :: StateExtensionEnv b <- return $ project s | |
| :compilation-0.0.0.3/Control/Compilation/Fresh.hs | |
| 44;9 9: i <- return $ project s | |
| :compilation-0.0.0.3/Control/Compilation/Sequences.hs | |
| 46;40 9: xss :: StateExtensionSequences b <- return $ project s | |
| 52;39 9: xs :: StateExtensionSequences b <- return $ project s | |
| 59;40 9: xss :: StateExtensionSequences b <- return $ project s | |
| :compilation-0.0.0.3/Control/Compilation/String.hs | |
| 47;14 9: (i, s) <- return $ project state | |
| 53;14 9: (i, s) <- return $ project state | |
| 59;14 9: (i, s) <- return $ project state | |
| 65;14 9: (i, s) <- return $ project state | |
| 71;14 9: (i, s) <- return $ project state | |
| 77;14 9: (i, s) <- return $ project state | |
| 83;14 9: (i, s) <- return $ project state | |
| :computational-algebra-0.3.0.0/examples/bench.hs | |
| 30;9 9: ideal1 <- return $! (i1 `using` rdeepseq) | |
| 31;9 9: ideal2 <- return $! (i2 `using` rdeepseq) | |
| 32;9 9: ideal3 <- return $! (i3 `using` rdeepseq) | |
| 33;9 9: ideal4 <- return $! (i4 `using` rdeepseq) | |
| :computational-algebra-0.3.0.0/examples/elimination-bench.hs | |
| 40;9 9: ideal1 <- return $! (i1 `using` rdeepseq) | |
| 41;9 9: ideal2 <- return $! (i2 `using` rdeepseq) | |
| 42;9 9: ideal3 <- return $! (i3 `using` rdeepseq) | |
| 43;9 9: ideal4 <- return $! (i4 `using` rdeepseq) | |
| 44;24 9: [var_x, var_y, var_t] <- return $! (map (flip Variable Nothing) "xyt" `using` rdeepseq) | |
| :computational-algebra-0.3.0.0/examples/sugar-bench.hs | |
| 44;9 9: ideal1 <- return $! (i1 `using` rdeepseq) | |
| 45;9 9: ideal2 <- return $! (i2 `using` rdeepseq) | |
| 46;9 9: ideal3 <- return $! (i3 `using` rdeepseq) | |
| 47;9 9: ideal4 <- return $! (i4 `using` rdeepseq) | |
| :computational-algebra-0.3.0.0/examples/sugar-paper.hs | |
| 62;9 9: ideal1 <- return $! (i1 `using` rdeepseq) | |
| 63;9 9: ideal2 <- return $! (i2 `using` rdeepseq) | |
| 64;9 9: ideal3 <- return $! (i3 `using` rdeepseq) | |
| 65;9 9: ideal4 <- return $! (i4 `using` rdeepseq) | |
| :computational-algebra-0.3.0.0/examples/sugar.hs | |
| 30;9 9: ideal1 <- return $! (i1 `using` rdeepseq) | |
| 31;9 9: ideal2 <- return $! (i2 `using` rdeepseq) | |
| 32;9 9: ideal3 <- return $! (i3 `using` rdeepseq) | |
| 33;9 9: ideal4 <- return $! (i4 `using` rdeepseq) | |
| :computations-0.0.0.0/src/Control/Computation/Resourceful.hs | |
| 487;39 9: AtomicResource (Gen hdl') <- return $ | |
| :ConcurrentUtils-0.4.4.0/Control/CUtils/FChan.hs | |
| 34;5 9: may <- return (Just chn) | |
| :ConcurrentUtils-0.4.4.0/Control/CUtils/NetChan.hs | |
| 307;6 9: cert <- return $ fromChunks [cert] | |
| 335;7 9: salt <- return $ readSecureMem salt | |
| :conduit-1.2.6.6/test/main.hs | |
| 980;16 9: res <- return () C.$$ sink | |
| :Control-Engine-1.1.0.1/Control/ThreadPool.hs | |
| 18;5 9: o <- return $! mutator i | |
| :copilot-c99-2.2.0/src/Copilot/Compile/C99/MetaTable.hs | |
| 110;15 9: W.ExprInst <- return (W.exprInst t) | |
| 128;19 9: W.ExprInst <- return (W.exprInst t) | |
| 139;15 9: W.ExprInst <- return (W.exprInst elemType) | |
| 150;15 9: W.ExprInst <- return (W.exprInst t) | |
| :copilot-c99-2.2.0/src/Copilot/Compile/C99/Phases.hs | |
| 69;21 9: W.AssignInst <- return $ W.assignInst t | |
| 83;24 9: W.IntegralEInst <- return $ W.integralEInst idxType | |
| 84;21 9: W.AssignInst <- return $ W.assignInst elemType | |
| 85;19 9: W.ExprInst <- return $ W.exprInst elemType | |
| 125;21 9: W.AssignInst <- return $ W.assignInst t | |
| 158;21 9: W.AssignInst <- return (W.assignInst t2) | |
| 159;18 9: Just Refl <- return (t1 =~= t2) | |
| 216;21 9: W.AssignInst <- return (W.assignInst t) | |
| 245;21 9: W.AssignInst <- return (W.assignInst t) | |
| :copilot-sbv-2.2.0/src/Copilot/Compile/SBV/Code.hs | |
| 64;18 9: W.SymWordInst <- return (W.symWordInst t2) | |
| 65;25 9: W.HasSignAndSizeInst <- return (W.hasSignAndSizeInst t2) | |
| 66;11 9: Just p <- return (t1 =~= t2) | |
| 88;22 9: W.SymWordInst <- return (W.symWordInst t) | |
| 89;29 9: W.HasSignAndSizeInst <- return (W.hasSignAndSizeInst t) | |
| 125;18 9: W.SymWordInst <- return (W.symWordInst t) | |
| 126;25 9: W.HasSignAndSizeInst <- return (W.hasSignAndSizeInst t) | |
| 149;20 9: W.SymWordInst <- return (W.symWordInst t) | |
| 150;27 9: W.HasSignAndSizeInst <- return (W.hasSignAndSizeInst t) | |
| 263;27 9: W.SymWordInst <- return (W.symWordInst t) | |
| 264;27 9: W.HasSignAndSizeInst <- return (W.hasSignAndSizeInst t) | |
| 272;23 9: W.SymWordInst <- return (W.symWordInst t) | |
| 273;23 9: W.HasSignAndSizeInst <- return (W.hasSignAndSizeInst t) | |
| :cpphs-1.20.1/cpphs.hs | |
| 28;7 9: args <- return $ if "--cpp" `elem` args then convertArgs args else args | |
| :cpphs-1.20.1/Language/Preprocessor/Cpphs/MacroPass.hs | |
| 134;25 9: "__DATE__" -> do w <- return . | |
| 138;25 9: "__TIME__" -> do w <- return . | |
| :Craft3e-0.1.0.10/Chapter18.hs | |
| 252;11 9: = do num <- return n | |
| :Craft3e-0.1.0.10/UseMonads.hs | |
| 16;16 8,47 8:example5 = do {x<-return 'c':: Identity Char; y<-return 'd';return [x,y]} | |
| 18;16 8,44 8:example6 = do {x<-return 'c':: Maybe Char; y<-return 'd';return [x,y]} | |
| 20;16 8,41 8:example7 = do {x<-return 'c':: IO Char; y<-return 'd';return [x,y]} | |
| 22;16 8,40 8:example8 = do {x<-return 'c':: [Char]; y<-return 'd';return [x,y]} | |
| :crypto-pubkey-0.2.8/Crypto/PubKey/ECC/Prim.hs | |
| 71;10 9: s <- return . addF2m xp =<< divF2m fx yp xp | |
| :cryptol-2.3.0/src/Cryptol/Symbolic.hs | |
| 165;35 9: b <- return $! fromVBit (foldl fromVFun v args) | |
| 214;15 9: b <- return $! fromVBit (foldl fromVFun v args) | |
| :cryptol-2.3.0/src/Cryptol/TypeCheck/Monad.hs | |
| 91;12 9: do rec ro <- return RO { iRange = inpRange info | |
| :cryptonite-0.15/Crypto/PubKey/ECC/Prim.hs | |
| 81;10 9: s <- return . addF2m xp =<< divF2m fx yp xp | |
| :curry-frontend-0.2.12/src/CurryBuilder.hs | |
| 44;16 9: (cfile, errs1) <- return (maybe ("", [missingModule file]) | |
| :daemonize-doublefork-0.1.1/System/Posix/Daemon.hs | |
| 124;11 9: pid <- return . read =<< readFile pidFile | |
| :dao-0.1.0.1/src/Dao/Interpreter.hs | |
| 6694;17 9: newValue <- return $ M.lookup name $ head $ mapList ref | |
| :dao-0.1.0.1/src/Dao/Lib/ListEditor.hs | |
| 133;17 9: (changed, o) <- return $ unzip o | |
| :dao-0.1.0.1/src/Dao/PPrint.hs | |
| 317;7 9: st <- return (st{printerBuf = printerBuf st}) | |
| :dao-0.1.0.1/src/Dao/Random.hs | |
| 435;9 9: minlen <- return (min minlen maxlen) | |
| 436;9 9: maxlen <- return (max minlen maxlen) | |
| :dao-0.1.0.1/src/Dao/StepList.hs | |
| 153;19 9: (lo, hi) <- return bnds | |
| 154;19 9: (lo, hi) <- return (min lo hi, max lo hi) | |
| :dao-0.1.0.1/src/dao-main.hs | |
| 87;7 9: argv <- return $ fmap ustr $ filter (/="--version") argv | |
| :Dao-0.1.0.2/src/Dao/Lib/ListEditor.hs | |
| 133;17 9: (changed, o) <- return $ unzip o | |
| :Dao-0.1.0.2/src/Dao/Interpreter.hs | |
| 6694;17 9: newValue <- return $ M.lookup name $ head $ mapList ref | |
| :Dao-0.1.0.2/src/Dao/PPrint.hs | |
| 317;7 9: st <- return (st{printerBuf = printerBuf st}) | |
| :Dao-0.1.0.2/src/Dao/Random.hs | |
| 435;9 9: minlen <- return (min minlen maxlen) | |
| 436;9 9: maxlen <- return (max minlen maxlen) | |
| :Dao-0.1.0.2/src/Dao/StepList.hs | |
| 153;19 9: (lo, hi) <- return bnds | |
| 154;19 9: (lo, hi) <- return (min lo hi, max lo hi) | |
| :Dao-0.1.0.2/src/dao-main.hs | |
| 87;7 9: argv <- return $ fmap ustr $ filter (/="--version") argv | |
| :darcs-2.12.0/harness/Darcs/Test/Patch/Arbitrary/Generic.hs | |
| 80;48 9: ps2' :/\: ps1' <- return $ merge (ps1 :\/: ps2) | |
| :darcs-2.12.0/harness/Darcs/Test/Patch/Properties/RepoPatchV2.hs | |
| 32;24 9: do Sealed (G2 flat) <- return $ flattenTree $ mapTree prim2repopatchV2 t | |
| 33;11 9: rms <- return $ map (start `repoApply`) flat | |
| :darcs-2.12.0/harness/Darcs/Test/Patch/Properties/V1Set2.hs | |
| 162;25 9: IsEq <- return $ p1o =\/= p1 | |
| 165;25 9: IsEq <- return $ p2 =\/= p2b | |
| 166;25 9: IsEq <- return $ p1'a =\/= p1'b | |
| 252;38 9: IsEq <- return $ invert ip1' =/\= p1' | |
| 253;38 9: IsEq <- return $ invert ip2' =/\= p2' | |
| 254;38 9: IsEq <- return $ ip1o' =/\= ip1' | |
| 255;38 9: IsEq <- return $ p2o =\/= p2 | |
| 256;38 9: IsEq <- return $ p1'' =/\= p1 | |
| 257;38 9: IsEq <- return $ ip2x' =\/= ip2' | |
| 278;35 9: IsEq <- return $ invert ip1' =/\= p1' | |
| 279;35 9: IsEq <- return $ invert ip2' =/\= p2' | |
| 280;35 9: IsEq <- return $ ip1o' =/\= ip1' | |
| 281;35 9: IsEq <- return $ p2o =\/= p2 | |
| 282;35 9: IsEq <- return $ p1'' =/\= p1 | |
| 283;35 9: IsEq <- return $ ip2x' =\/= ip2' | |
| :darcs-2.12.0/src/Darcs/Patch/Depends.hs | |
| 495;9 9: IsEq <- return (a'' =\/= a) | |
| 520;9 9: IsEq <- return (a'' =/\= a) | |
| :darcs-2.12.0/src/Darcs/Patch/Rebase/Fixup.hs | |
| 100;17 9: q' :> p' <- return $ commutePrimName (p :> q) | |
| 104;17 9: q' :> p' <- return $ commuteNamePrim (p :> q) | |
| :darcs-2.12.0/src/Darcs/Patch/Rebase/Viewing.hs | |
| 351;55 9: fixupsS :> (fixups2'' :> edit2'') :> fixups1' <- return $ pushThrough (fixups1 :> (fixups2' :> edit2')) | |
| :darcs-2.12.0/src/Darcs/Patch/V1/Commute.hs | |
| 458;24 9: isHunk p = do PP p' <- return p | |
| :darcs-2.12.0/src/Darcs/Patch/V1/Read.hs | |
| 37;27 9: Sealed m <- return $ merger (BC.unpack g) p1 p2 | |
| :darcs-2.12.0/src/Darcs/Patch/V2/Non.hs | |
| 193;16 9:-- > n1' :> n2' <- return $ filterConflictsFL p2ooo n2n1 | |
| :darcs-2.12.0/src/Darcs/Patch/V2/RepoPatch.hs | |
| 242;33 9: NilFL <- return pa | |
| 245;33 9: do NilFL <- return goneby | |
| 246;33 9: NilFL <- return $ joinEffects (ps :<: p) | |
| 256;41 9: NilFL <- return pa | |
| 445;14 9: False <- return $ any (conflictsWith y) (x':ix') | |
| 446;14 9: False <- return $ any (conflictsWith x') iy | |
| 457;14 9: False <- return $ any (conflictsWith y') (x':ix') | |
| 458;14 9: False <- return $ any (conflictsWith x') iy' | |
| 465;14 9: False <- return $ any (conflictsWith y') (x':ix') | |
| 466;14 9: False <- return $ any (conflictsWith x') iy' | |
| 607;23 9: n1' :> n2' <- return $ filterConflictsFL p2ooo n2n1 | |
| 944;28 9: isHunk rp = do Normal p <- return rp | |
| :darcs-2.12.0/src/Darcs/Repository/Clone.hs | |
| 252;17 9: _ :> us' <- return $ findCommonWithThem patches context | |
| :darcs-2.12.0/src/Darcs/Repository/Internal.hs | |
| 438;18 9: Sealed sfp <- return $ siftForPending origp | |
| 469;20 9: Sealed x <- return $ sift NilFL $ reverseFL oldps | |
| 541;19 9: Sealed newpend <- return $ rmpend (progressFL "Removing from pending:" effectp) | |
| 739;29 9: FlippedSeal newpend_ <- return $ | |
| 756;17 9: Sealed prims <- return $ siftForPending patch | |
| 773;20 9: Sealed newpend_ <- return $ newpend (unsafeCoerceP pend) patch | |
| 857;25 9: Sealed new_pending <- return $ siftForPending tpend | |
| :darcs-2.12.0/src/Darcs/Repository/Merge.hs | |
| 84;9 9: <- return $ merge2FL (progressFL "Merging us" usi) | |
| 88;18 9: pend' :/\: pw <- return $ merge (pc :\/: anonpend :>: NilFL) | |
| 91;32 9: Sealed standard_resolved_pw <- return $ standardResolution pwprim | |
| :darcs-2.12.0/src/Darcs/Repository/Rebase.hs | |
| 156;20 9: (_, Sealed2 ps) <- return $ takeAnyRebase allpatches | |
| 184;29 9: Just (ps' :> r') <- return $ commuterIdRL selfCommuter (r :> ps) | |
| 197;20 9: (_, Sealed2 ps) <- return $ takeAnyRebase allpatches | |
| :darcs-2.12.0/src/Darcs/Repository/State.hs | |
| 211;9 9: IsEq <- return $ workDirLessRepoWitness r | |
| 228;7 9: IsEq <- return (unsafeCoerceP IsEq) :: IO (EqCheck wY wU) | |
| 410;24 9: them' :> rest <- return $ partitionConflictingFL commuter them (us :<: unrec) | |
| 511;15 9: _ :> hunks <- return $ partitionRL primIsHunk $ reverseFL changes | |
| :darcs-2.12.0/src/Darcs/UI/Commands/Add.hs | |
| 303;24 9: Sealed p' <- return $ unFreeLeft p | |
| :darcs-2.12.0/src/Darcs/UI/Commands/Apply.hs | |
| 290;14 9: common :> _ <- return $ findCommonWithThem us them | |
| 306;17 9: (us':\/:them') <- return $ findUncommon us them | |
| :darcs-2.12.0/src/Darcs/UI/Commands/Convert.hs | |
| 920;33 9: (prims :: FL p cX cY) <- return $ fromPrims $ sortCoalesceFL $ reverseRL ps | |
| :darcs-2.12.0/src/Darcs/UI/Commands/Diff.hs | |
| 216;13 9: Sealed all <- return $ case (secondMatch matchFlags, patchset) of | |
| 220;13 9: Sealed ctx <- return $ if firstMatch matchFlags | |
| 224;15 9: Sealed match <- return $ if secondMatch matchFlags | |
| 228;16 9: (_ :> todiff) <- return $ findCommonWithThem match ctx | |
| 229;19 9: (_ :> tounapply) <- return $ findCommonWithThem all match | |
| :darcs-2.12.0/src/Darcs/UI/Commands/MarkConflicts.hs | |
| 142;13 9: Sealed res <- return $ patchsetConflictResolutions r | |
| :darcs-2.12.0/src/Darcs/UI/Commands/Pull.hs | |
| 396;14 9: common :> _ <- return $ findCommonWithThem us them | |
| 397;17 9: us' :\/: them' <- return $ findUncommon us them | |
| 398;18 9: _ :\/: compl' <- return $ findUncommon us compl | |
| 401;10 9: ps :> _ <- return $ partitionFL (not . (`elem` avoided) . info) them' | |
| :darcs-2.12.0/src/Darcs/UI/Commands/Push.hs | |
| 219;16 9: common :> us' <- return $ findCommonWithThem us them | |
| :darcs-2.12.0/src/Darcs/UI/Commands/Rebase.hs | |
| 228;39 9: (rOld, suspended, allpatches_tail) <- return $ takeHeadRebase allpatches | |
| 412;24 9: (rOld, Items ps, _) <- return $ takeHeadRebase patches | |
| 448;31 9: Sealed standard_resolved_p <- return $ standardResolution $ concatFL | |
| 519;61 9: Just (ps2 :> (rename2 :: RebaseName p wV wT2)) <- return (commuterIdFL (commuterIdWDD commuteNameNamed) (rename :> ps)) | |
| 521;19 9: IsEq <- return (unsafeCoerceP IsEq :: EqCheck wV wT2) | |
| 573;24 9: (rOld, Items ps, _) <- return $ takeHeadRebase patches | |
| 587;21 9: fixups :> toedit <- return $ extractSingle chosens | |
| 589;31 9: name_fixups :> prim_fixups <- return $ flToNamesPrims fixups | |
| 655;24 9: (rOld, Items ps, _) <- return $ takeHeadRebase patches | |
| 947;25 9: usOk :> usConflicted <- return $ partitionConflictingFL (commuterIdFL selfCommuter) us' to_be_applied | |
| 963;25 9: (rOld, suspended, _) <- return $ takeHeadRebaseFL us' | |
| 1066;25 9: (_, Items ps, _) <- return $ takeHeadRebase patches | |
| :darcs-2.12.0/src/Darcs/UI/Commands/Revert.hs | |
| 146;26 9: Sealed touching_changes <- return (chooseTouching pre_changed_files changes) | |
| :darcs-2.12.0/src/Darcs/UI/Commands/Rollback.hs | |
| 160;23 9: (_ :> patches) <- return $ | |
| :darcs-2.12.0/src/Darcs/UI/Commands/Send.hs | |
| 308;16 9: common :> us' <- return $ findCommonWithThem us them | |
| :darcs-2.12.0/src/Darcs/UI/Commands/Unrecord.hs | |
| 154;27 9: (_ :> patches) <- return $ | |
| :darcs-2.12.0/src/Darcs/UI/Commands/Unrevert.hs | |
| 159;16 9: Sealed h_them <- return $ mergeThem us them | |
| :darcs-2.12.0/src/Darcs/UI/Commands/WhatsNew.hs | |
| 272;18 9: adds :> _ <- return $ partitionRL primIsHunk $ reverseFL ps | |
| 298;24 9: Sealed res <- return $ patchsetConflictResolutions r | |
| :darcs-2.12.0/src/Darcs/UI/SelectChanges.hs | |
| 764;31 9: (first_chs :> _ :> last_chs) <- return $ getChoices c | |
| 1068;17 9: FlippedSeal ps <- return | |
| 1078;14 9: Sealed2 ps' <- return $ case getChoices (forceFirsts tas pc) of _ :> mc :> _ -> Sealed2 $ mapFL_FL lpPatch mc | |
| :darcs-2.12.0/src/Darcs/Util/Download/Request.hs | |
| 68;11 9: x : xs <- return $ reverse ys | |
| :darcs-beta-2.7.99.2/src/Darcs/Commands/Add.hs | |
| 258;24 9: Sealed p' <- return $ unFreeLeft p | |
| :darcs-beta-2.7.99.2/src/Darcs/Commands/Apply.hs | |
| 190;14 9: common :> _ <- return $ findCommonWithThem us them | |
| 206;17 9: (us':\/:them') <- return $ findUncommon us them | |
| :darcs-beta-2.7.99.2/src/Darcs/Commands/Get.hs | |
| 252;16 9: _ :> us' <- return $ findCommonWithThem patches context | |
| :darcs-beta-2.7.99.2/src/Darcs/Commands/MarkConflicts.hs | |
| 88;13 9: Sealed res <- return $ patchsetConflictResolutions r | |
| :darcs-beta-2.7.99.2/src/Darcs/Commands/Optimize.hs | |
| 230;21 9: do some_siblings <- return (flagsToSiblings opts) | |
| 232;16 9: siblings <- return (map toFilePath some_siblings ++ defrepolist) | |
| :darcs-beta-2.7.99.2/src/Darcs/Commands/Pull.hs | |
| 246;14 9: common :> _ <- return $ findCommonWithThem us them | |
| 247;17 9: us' :\/: them' <- return $ findUncommon us them | |
| 248;18 9: _ :\/: compl' <- return $ findUncommon us compl | |
| 251;10 9: ps :> _ <- return $ partitionFL (not . (`elem` avoided) . info) them' | |
| :darcs-beta-2.7.99.2/src/Darcs/Commands/Push.hs | |
| 131;16 9: common :> us' <- return $ findCommonWithThem us them | |
| :darcs-beta-2.7.99.2/src/Darcs/Commands/Put.hs | |
| 104;7 9: IsEq <- return (unsafeCoerceP IsEq) :: IO (EqCheck C(x1 x2)) | |
| :darcs-beta-2.7.99.2/src/Darcs/Commands/Record.hs | |
| 388;17 9: FlippedSeal ps <- return | |
| 398;14 9: Sealed2 ps' <- return $ case getChoices (forceFirsts tas pc) of _ :> mc :> _ -> Sealed2 $ mapFL_FL tpPatch mc | |
| :darcs-beta-2.7.99.2/src/Darcs/Commands/Revert.hs | |
| 92;26 9: Sealed touching_changes <- return (chooseTouching pre_changed_files changes) | |
| :darcs-beta-2.7.99.2/src/Darcs/Commands/Rollback.hs | |
| 116;17 9: (_ :> patches) <- return $ if firstMatch opts | |
| :darcs-beta-2.7.99.2/src/Darcs/Commands/Send.hs | |
| 170;16 9: common :> us' <- return $ findCommonWithThem us them | |
| :darcs-beta-2.7.99.2/src/Darcs/Commands/Unrecord.hs | |
| 102;17 9: (_ :> patches) <- return $ if firstMatch opts | |
| 194;36 9: (auto_kept :> removal_candidates) <- return $ | |
| :darcs-beta-2.7.99.2/src/Darcs/Commands/Unrevert.hs | |
| 94;16 9: Sealed h_them <- return $ mergeThem us them | |
| :darcs-beta-2.7.99.2/src/Darcs/Commands/WhatsNew.hs | |
| 146;18 9: adds :> _ <- return $ partitionRL primIsHunk $ reverseFL ps | |
| :darcs-beta-2.7.99.2/src/Darcs/Patch/Depends.hs | |
| 349;34 9: IsEq <- return (a'' =\/= a) | |
| 367;34 9: IsEq <- return (a'' =/\= a) | |
| :darcs-beta-2.7.99.2/src/Darcs/Patch/Merge.hs | |
| 35;20 9: ys' :/\: x' <- return $ mergeFL (x :\/: ys) | |
| 36;22 9: xs' :/\: ys'' <- return $ merge (ys' :\/: xs) | |
| 50;15 9: x' :/\: p' <- return $ merge (p :\/: x) | |
| 51;17 9: xs' :/\: p'' <- return $ mergeFL (p' :\/: xs) | |
| :darcs-beta-2.7.99.2/src/Darcs/Patch/V1/Commute.hs | |
| 407;24 9: isHunk p = do PP p' <- return p | |
| :darcs-beta-2.7.99.2/src/Darcs/Patch/V1/Read.hs | |
| 35;27 9: Sealed m <- return $ merger (BC.unpack g) p1 p2 | |
| :darcs-beta-2.7.99.2/src/Darcs/Patch/V2/Non.hs | |
| 190;16 9:-- > n1' :> n2' <- return $ filterConflictsFL p2ooo n2n1 | |
| :darcs-beta-2.7.99.2/src/Darcs/Patch/V2/Real.hs | |
| 234;33 9: NilFL <- return pa | |
| 237;33 9: do NilFL <- return goneby | |
| 238;33 9: NilFL <- return $ joinEffects (p :<: ps) | |
| 248;41 9: NilFL <- return pa | |
| 436;14 9: False <- return $ any (conflictsWith y) (x':ix') | |
| 437;14 9: False <- return $ any (conflictsWith x') iy | |
| 448;14 9: False <- return $ any (conflictsWith y') (x':ix') | |
| 449;14 9: False <- return $ any (conflictsWith x') iy' | |
| 456;14 9: False <- return $ any (conflictsWith y') (x':ix') | |
| 457;14 9: False <- return $ any (conflictsWith x') iy' | |
| 598;23 9: n1' :> n2' <- return $ filterConflictsFL p2ooo n2n1 | |
| 913;28 9: isHunk rp = do Normal p <- return rp | |
| :darcs-beta-2.7.99.2/src/Darcs/Repository/HashedRepo.hs | |
| 176;20 9: _ :> skipped <- return $ commuteToEnd (reverseFL to_remove) allpatches | |
| :darcs-beta-2.7.99.2/src/Darcs/Repository/Internal.hs | |
| 348;18 9: Sealed sfp <- return $ siftForPending origp | |
| 369;15 9: Sealed x <- return $ sfp NilFL $ reverseFL oldps | |
| 434;22 9: Sealed newpend <- return $ rmpend (progressFL "Removing from pending:" effectp) (unsafeCoercePStart pend) | |
| 553;27 9: FlippedSeal newpend_ <- return $ newpend (unsafeCoerceP pend :: FL (PrimOf p) C(a x)) patch | |
| 564;17 9: Sealed prims <- return $ siftForPending patch | |
| 575;23 9: Sealed newpend_ <- return $ newpend (unsafeCoerceP pend) patch | |
| 624;51 9: Sealed new_pending <- return $ siftForPending tpend | |
| :darcs-beta-2.7.99.2/src/Darcs/Repository/Merge.hs | |
| 60;15 9: Sealed pc <- return $ merge2FL (progressFL "Merging us" usi) (progressFL "Merging them" themi) | |
| 63;19 9: pend' :/\: pw <- return $ merge (pc :\/: anonpend :>: NilFL) | |
| 66;33 9: Sealed standard_resolved_pw <- return $ standardResolution pwprim | |
| :darcs-beta-2.7.99.2/src/Darcs/Repository/State.hs | |
| 160;9 9: IsEq <- return $ workDirLessRepoWitness r | |
| 190;7 9: IsEq <- return (unsafeCoerceP IsEq) :: IO (EqCheck C(y u)) | |
| :darcs-beta-2.7.99.2/src/Darcs/Repository.hs | |
| 268;17 9: us' :\/: them' <- return $ findUncommon us them | |
| :darcs-beta-2.7.99.2/src/Darcs/SelectChanges.hs | |
| 619;31 9: (first_chs :> _ :> last_chs) <- return $ getChoices c | |
| 898;24 9: them' :> rest <- return $ partitionConflictingFL commuter them (unrec :<: us) | |
| :darcs-beta-2.7.99.2/src/Darcs/Test/Patch/Arbitrary/Generic.hs | |
| 80;48 9: ps2' :/\: ps1' <- return $ merge (ps1 :\/: ps2) | |
| :darcs-beta-2.7.99.2/src/Darcs/Test/Patch/Properties/Real.hs | |
| 32;24 9: do Sealed (G2 flat) <- return $ flattenTree $ mapTree prim2real t | |
| 33;11 9: rms <- return $ map (start `repoApply`) flat | |
| :darcs-beta-2.7.99.2/src/Darcs/Test/Patch/Properties/V1Set2.hs | |
| 163;25 9: IsEq <- return $ p1o =\/= p1 | |
| 166;25 9: IsEq <- return $ p2 =\/= p2b | |
| 167;25 9: IsEq <- return $ p1'a =\/= p1'b | |
| 253;38 9: IsEq <- return $ invert ip1' =/\= p1' | |
| 254;38 9: IsEq <- return $ invert ip2' =/\= p2' | |
| 255;38 9: IsEq <- return $ ip1o' =/\= ip1' | |
| 256;38 9: IsEq <- return $ p2o =\/= p2 | |
| 257;38 9: IsEq <- return $ p1'' =/\= p1 | |
| 258;38 9: IsEq <- return $ ip2x' =\/= ip2' | |
| 278;35 9: IsEq <- return $ invert ip1' =/\= p1' | |
| 279;35 9: IsEq <- return $ invert ip2' =/\= p2' | |
| 280;35 9: IsEq <- return $ ip1o' =/\= ip1' | |
| 281;35 9: IsEq <- return $ p2o =\/= p2 | |
| 282;35 9: IsEq <- return $ p1'' =/\= p1 | |
| 283;35 9: IsEq <- return $ ip2x' =\/= ip2' | |
| :darcs-cabalized-2.0.2.2/src/Darcs/Commands/Apply.lhs | |
| 124;13 9: am_verbose <- return $ Verbose `elem` opts | |
| :darcs-cabalized-2.0.2.2/src/Darcs/Commands/Diff.lhs | |
| 189;10 9: thename <- return $ just_dir formerdir | |
| :darcs-cabalized-2.0.2.2/src/Darcs/Commands/Dist.lhs | |
| 88;7 9: verb <- return $ Verbose `elem` opts | |
| 91;13 9: resultfile <- return (formerdir++"/"++distname++".tar.gz") | |
| :darcs-cabalized-2.0.2.2/src/Darcs/Commands/MarkConflicts.lhs | |
| 77;13 9: Sealed res <- return $ patchset_conflict_resolutions r | |
| :darcs-cabalized-2.0.2.2/src/Darcs/Commands/Mv.lhs | |
| 97;12 9: [old,new] <- return $ case two_files of | |
| :darcs-cabalized-2.0.2.2/src/Darcs/Commands/Optimize.lhs | |
| 250;21 9: do some_siblings <- return (flagsToSiblings opts) | |
| 252;16 9: siblings <- return (some_siblings ++ defrepo) | |
| :darcs-cabalized-2.0.2.2/src/Darcs/Commands/Pull.lhs | |
| 128;23 9: (_, us' :\/: them'') <- return $ get_common_and_uncommon (us, them) | |
| 129;23 9: (_, _ :\/: compl') <- return $ get_common_and_uncommon (us, compl) | |
| 131;10 9: ps :> _ <- return $ partitionFL (not . (`elem` avoided) . info) $ reverseRL $ concatRL them'' | |
| :darcs-cabalized-2.0.2.2/src/Darcs/Commands/ShowContents.lhs | |
| 76;10 9: thename <- return $ just_dir formerdir | |
| :darcs-cabalized-2.0.2.2/src/Darcs/Commands/WhatsNew.lhs | |
| 106;18 9: cho_adds :> _ <- return $ partitionRL is_hunk $ reverseFL cho | |
| 107;13 9: cha :> _ <- return $ partitionRL is_hunk $ reverseFL $ select_files all_changes | |
| :darcs-cabalized-2.0.2.2/src/Darcs/Patch/Commute.lhs | |
| 794;24 9: isHunk p = do PP p' <- return p | |
| :darcs-cabalized-2.0.2.2/src/Darcs/Patch/Patchy.lhs | |
| 126;57 9: merge ((x:>:xs) :\/: ys) = fromJust $ do ys' :/\: x' <- return $ mergeFL (x :\/: ys) | |
| 127;59 9: xs' :/\: ys'' <- return $ merge (ys' :\/: xs) | |
| 133;55 9:mergeFL (p :\/: (x :>: xs)) = fromJust $ do x' :/\: p' <- return $ merge (p :\/: x) | |
| 134;57 9: xs' :/\: p'' <- return $ mergeFL (p' :\/: xs) | |
| :darcs-cabalized-2.0.2.2/src/Darcs/Patch/Prim.lhs | |
| 848;12 9: IsEq <- return $ p1o =\/= p1 | |
| 1160;16 9: IsEq <- return $ y'' =\/= y | |
| 1161;16 9: IsEq <- return $ ix'' =\/= invert x' | |
| :darcs-cabalized-2.0.2.2/src/Darcs/Patch/QuickCheck.lhs | |
| 296;24 9: do Sealed (G2 flat) <- return $ flattenTree $ mapTree prim2real t | |
| 297;11 9: rms <- return $ map (applyPatch start) flat | |
| 376;48 9: ps2' :/\: ps1' <- return $ merge (ps1 :\/: ps2) | |
| :darcs-cabalized-2.0.2.2/src/Darcs/Patch/Real.lhs | |
| 148;59 9: NilFL <- return $ sort_coalesceFL $ effect $ p':<:a | |
| 150;68 9: `mplus` do NilFL <- return goneby | |
| 151;68 9: NilFL <- return $ sort_coalesceFL $ | |
| 165;59 9: NilFL <- return $ sort_coalesceFL $ effect $ p':<:a | |
| 301;17 9: False <- return $ any (conflicts_with y) (x':ix') | |
| 302;17 9: False <- return $ any (conflicts_with x') iy | |
| 311;17 9: False <- return $ any (conflicts_with y') (x':ix') | |
| 312;17 9: False <- return $ any (conflicts_with x') iy' | |
| 319;17 9: False <- return $ any (conflicts_with y') (x':ix') | |
| 320;17 9: False <- return $ any (conflicts_with x') iy' | |
| 442;28 9: n1' :> n2' <- return $ filterConflictsFL p2ooo n2n1 | |
| 719;28 9: isHunk rp = do Normal p <- return rp | |
| :darcs-cabalized-2.0.2.2/src/Darcs/Repository/Checkpoint.lhs | |
| 82;6 9: pis <- return $ reverse $ read_patch_ids pistr | |
| :darcs-cabalized-2.0.2.2/src/Darcs/Repository/DarcsRepo.lhs | |
| 157;12 9: tagname <- return $ make_filename $ last $ mapRL info ps | |
| 197;29 9: skipped :< unmodified <- return $ commute_to_end (unsafeCoerceP to_remove) allpatches | |
| 260;8 9: pis <- return $ reverse $ read_patch_ids str | |
| 304;6 9: pis <- return $ reverse $ read_patch_ids pistr | |
| :darcs-cabalized-2.0.2.2/src/Darcs/Repository/HashedRepo.lhs | |
| 125;20 9: skipped :< _ <- return $ commute_to_end to_remove allpatches | |
| :darcs-cabalized-2.0.2.2/src/Darcs/Repository/Internal.lhs | |
| 397;22 9: Sealed newpend <- return $ rmpend (progressFL "Removing from pending:" effectp) pend | |
| 442;19 9: pend' :/\: pw <- return $ merge (pc :\/: anonymous (fromPrims pend) :>: NilFL) | |
| :darcs-cabalized-2.0.2.2/src/Darcs/Repository/Prefs.lhs | |
| 289;12 9: regexes <- return (map (\r -> mkRegex r) (bins ++ gbs)) | |
| :darcs-fastconvert-0.2.1/Import.hs | |
| 246;16 9: prims <- return $ fromPrims $ sortCoalesceFL diff | |
| :data-flags-0.0.3.1/src/Data/Flags/TH.hs | |
| 65;11 9: typeName <- return $ mkName typeNameS | |
| :Data-Hash-Consistent-0.1.1/Data/Hash/Consistent.hs | |
| 28;7 9: ch <- return $ CH.add hosts n ch | |
| 33;7 9: ch <- return $ CH.del fh n ch | |
| :Data-Hash-Consistent-0.1.1/example.hs | |
| 8;7 9: ch <- return $ CH.add hosts n ch | |
| 13;7 9: ch <- return $ CH.del fh n ch | |
| :data-object-yaml-0.3.4.2/runtests.hs | |
| 175;30 9: Just (Mapping ((x, _):_)) <- return $ decodeYaml inOrderData | |
| :data-spacepart-20090215.0/test/Render.hs | |
| 92;20 9: window_size <- return . fromJust . mwindow_size =<< readIORef viewer_ref | |
| :data-stringmap-1.0.1.1/benchmarks/StringMap.hs | |
| 20;9 9: keys <- return $ lines dict | |
| 21;10 9: elems <- return $ zip keys [1..] | |
| 22;6 9: m <- return $ (M.fromList elems :: M.StringMap Int) | |
| :ddc-core-llvm-0.4.2.2/DDC/Core/Llvm/Convert/Exp/Case.hs | |
| 98;32 9: lAlt <- return (altResultLabel alt') | |
| :ddc-core-simpl-0.4.2.1/DDC/Core/Transform/Rewrite.hs | |
| 462;16 9: l:ls <- return $ X.takeXAppsAsList lhs | |
| :debian-3.89/debian/Control/Policy.hs | |
| 61;14 9: try (do _ <- return $ debianPackageNames (DebianControl ctl) | |
| 62;14 9: _ <- return $ debianBuildDeps (DebianControl ctl) | |
| 63;14 9: _ <- return $ debianBuildDepsIndep (DebianControl ctl) | |
| :debian-3.89/utils/Report.hs | |
| 75;21 9: do columns <- return . fromMaybe 80 =<< getWidth | |
| :dedukti-1.1.4/Dedukti/Analysis/Dependency.hs | |
| 17;43 9: , Just m <- return (provenance x) ] | |
| :derive-2.5.25/src/Data/Derive/DSL/SYB.hs | |
| 45;12 9: List xs <- return x | |
| 51;25 9: App name (List args) <- return x | |
| 71;24 9: Instance _ name bod <- return x | |
| 81;13 9: String x <- return x | |
| 87;34 9: App "List" (List [MapCtor x]) <- return x | |
| 103;26 9: Application (List xs) <- return x | |
| :derive-2.5.25/src/Derive/Generate.hs | |
| 21;7 9: xs <- return $ sort [x | x <- xs, takeExtension x == ".hs", x /= "All.hs", takeBaseName x `notElem` evil] | |
| :derive-2.5.25/src/Derive/Main.hs | |
| 37;8 9: src <- return $ unlines $ filter (not . isPrefixOf "#") $ lines src | |
| 41;10 9: flags <- return $ foldl addFlags flags | |
| :derive-2.5.25/src/Derive/Utils.hs | |
| 32;8 9: src <- return $ takeWhile (/= "-}") $ drop 1 $ dropWhile (/= "{-") $ | |
| :derive-gadt-0.1.1/src/derive-gadt.hs | |
| 16;13 9: (opts,_,_) <- return . getOpt Permute options =<< getArgs | |
| :derive-gadt-0.1.1/tools/hstidy.hs | |
| 28;13 9: (opts,_,_) <- return . getOpt Permute options =<< getArgs | |
| :direct-http-0.6/Network/HTTP.hs | |
| 726;14 9: identString <- return "-" | |
| 727;17 9: usernameString <- return "-" | |
| 737;20 9: maybeResponseSize <- return (Nothing :: Maybe Int) -- TODO | |
| 1022;26 9: (result, inputBuffer) <- return $ BS.splitAt length inputBuffer | |
| 1584;21 9: (result, buffer) <- return $ case maybeSize of | |
| 1757;18 9: headerMap <- return $ Map.delete header headerMap | |
| :direct-murmur-hash-1.0.1/Data/Digest/Murmur3.hs | |
| 61;11 9: k1 <- return $ k1 * c1 | |
| 62;11 9: k1 <- return $ rotateL k1 31 | |
| 63;11 9: k1 <- return $ k1 * c2 | |
| 64;11 9: h1 <- return $ xor h1 k1 | |
| 66;11 9: h1 <- return $ rotateL h1 27 | |
| 67;11 9: h1 <- return $ h1 + h2 | |
| 68;11 9: h1 <- return $ h1 * 5 + 0x52dce729 | |
| 70;11 9: k2 <- return $ k2 * c2 | |
| 71;11 9: k2 <- return $ rotateL k2 33 | |
| 72;11 9: k2 <- return $ k2 * c1 | |
| 73;11 9: h2 <- return $ xor h2 k2 | |
| 75;11 9: h2 <- return $ rotateL h2 31 | |
| 76;11 9: h2 <- return $ h2 + h1 | |
| 77;11 9: h2 <- return $ h2 * 5 + 0x38495ab5 | |
| 84;11 9: k1 <- return $ k1 * c1 | |
| 85;11 9: k1 <- return $ rotateL k1 31 | |
| 86;11 9: k1 <- return $ k1 * c2 | |
| 87;11 9: h1 <- return $ xor h1 k1 | |
| 89;11 9: k2 <- return $ k2 * c2 | |
| 90;11 9: k2 <- return $ rotateL k2 33 | |
| 91;11 9: k2 <- return $ k2 * c1 | |
| 92;11 9: h2 <- return $ xor h2 k2 | |
| 94;11 9: h1 <- return $ xor h1 totalLength | |
| 95;11 9: h2 <- return $ xor h2 totalLength | |
| 98;11 9: h1 <- return $ h1 + h2 | |
| 99;11 9: h2 <- return $ h2 + h1 | |
| 103;10 9: k <- return $ xor k (shiftR k 33) | |
| 104;10 9: k <- return $ k * 0xff51afd7ed558ccd | |
| 105;10 9: k <- return $ xor k (shiftR k 33) | |
| 106;10 9: k <- return $ k * 0xc4ceb9fe1a85ec53 | |
| 107;10 9: k <- return $ xor k (shiftR k 33) | |
| :direct-sqlite-2.3.17/test/Main.hs | |
| 695;9 9: True <- return $ (`notElem` [1, 123, maxBound]) rowid | |
| :DirectSound-0.0.0/Sound/Win32/DirectSound.hs | |
| 358;6 9: q <- return p; | |
| 359;32 9: qif <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 360;32 9: arf <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 361;32 9: rel <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 362;32 9: csb <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 363;32 9: gcp <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 364;32 9: dsb <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 365;32 9: scl <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 366;32 9: cpt <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 367;32 9: gsc <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 368;32 9: ssc <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 369;32 9: ini <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 370;32 9: vcf <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 590;6 9: q <- return p; | |
| 591;32 9: qif <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 592;32 9: arf <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 593;32 9: rel <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 595;32 9: cap <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 596;32 9: gcp <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 597;32 9: gft <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 598;32 9: gvl <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 599;32 9: gpn <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 600;32 9: gfr <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 601;32 9: gst <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 602;32 9: ini <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 603;32 9: lck <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 604;32 9: ply <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 605;32 9: scp <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 606;32 9: sft <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 607;32 9: svl <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 608;32 9: spn <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 609;32 9: sfr <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 610;32 9: stp <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 611;32 9: ulk <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 612;32 9: rst <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 614;32 9: sfx <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 615;32 9: aqr <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| 616;32 9: gop <- peek (castPtr q) ; q <- return (q `plusPtr` k) | |
| :distributed-process-0.6.1/src/Control/Distributed/Process/Management/Internal/Trace/Tracer.hs | |
| 152;10 9: msg <- return $ (formatTime defaultTimeLocale "%c" now, buildTxt ev) | |
| 153;15 9: emptyPid <- return $ (nullProcessId (localNodeId node)) | |
| 154;15 9: traceMsg <- return $ NCMsg { | |
| :distributed-process-lifted-0.2.0.1/test/Control/Distributed/Process/Lifted/Tests.hs | |
| 144;21 9: True <- return $ Just ref' == ref && pid == theirAddr && mOrL && reason == reason' | |
| 148;17 9: True <- return $ pid == theirAddr && not mOrL && not un && reason == reason' | |
| 370;11 9: True <- return $ pid' == server2 | |
| 468;13 9: True <- return $ xs == expected | |
| 481;13 9: True <- return $ xs == expected | |
| 525;13 9: True <- return $ xs == "abcacbbacbcacabcba" | |
| 553;9 9: True <- return $ ref == ref' && pid == pid' && ex == show ProcessTerminationException | |
| 568;9 9: True <- return $ ref == ref' && nid == localNodeId node1 | |
| 583;9 9: True <- return $ ref == ref' && nid == localNodeId node1 | |
| 622;9 9: True <- return $ pingServer == pid | |
| 626;9 9: True <- return $ pingServer == pid' | |
| 647;9 9: True <- return $ pingServer == pid | |
| 651;9 9: True <- return $ pingServer == pid' | |
| 799;9 9: True <- return $ msg1 == "message 1" && msg2 == "message 3" | |
| 1154;9 9: True <- return $ ref == ref' && pid == pid' && ex == "killed-by=" ++ show us ++ ",reason=TestKill" | |
| 1173;9 9: True <- return $ ref == ref' && pid == pid' && reason == "killed-by=" ++ show us ++ ",reason=TestKill" | |
| 1268;18 9: True <- return $ reason == ("foobar", 123 :: Int) | |
| 1283;13 9: True <- return $ reason == ("foobar", 123 :: Int) | |
| 1298;15 9: True <- return $ (show ex) == expected | |
| 1313;13 9: True <- return $ reason == "TestExit" | |
| 1321;9 9: True <- return $ ref == ref' && pid == pid' | |
| 1338;13 9: True <- return $ reason == "TestExit" | |
| 1345;9 9: True <- return $ ref == ref' && pid == pid' | |
| :distributed-process-platform-0.1.0/src/Control/Distributed/Process/Platform/Task/Queue/BlockingQueue.hs | |
| 158;16 9: taskEntry <- return (ref, from, asyncHandle) | |
| :distributed-process-platform-0.1.0/tests/TestTaskQueues.hs | |
| 61;6 9: job <- return $ ($(mkClosure 'sampleTask) (seconds 2, "foobar")) | |
| 70;7 9: job1 <- return $ ($(mkClosure 'namedTask) ("job1", "foo")) | |
| 71;7 9: job2 <- return $ ($(mkClosure 'namedTask) ("job2", "bar")) | |
| 103;8 9: job <- return $ ($(mkClosure 'crashingTask) sp) | |
| :distributed-process-task-0.1.2.2/src/Control/Distributed/Process/Task/Queue/BlockingQueue.hs | |
| 158;16 9: taskEntry <- return (ref, from, asyncHandle) | |
| :distributed-process-task-0.1.2.2/tests/TestTaskQueues.hs | |
| 61;6 9: job <- return $ ($(mkClosure 'sampleTask) (seconds 2, "foobar")) | |
| 70;7 9: job1 <- return $ ($(mkClosure 'namedTask) ("job1", "foo")) | |
| 71;7 9: job2 <- return $ ($(mkClosure 'namedTask) ("job2", "bar")) | |
| 103;8 9: job <- return $ ($(mkClosure 'crashingTask) sp) | |
| :distributed-process-tests-0.4.5/src/Control/Distributed/Process/Tests/Closure.hs | |
| 197;9 9: 13 <- return $ fn 6 | |
| 272;11 9: True <- return $ pid' == pid'' | |
| 297;11 9: True <- return $ pid' == pid'' | |
| 409;11 9: True <- return $ ref' == ref | |
| 427;9 9: True <- return $ ref' == ref && pid == pid' | |
| 504;9 9: True <- return $ count == 2 || count == 3 -- It depends on which message we get first in 'spawn' | |
| :distributed-process-tests-0.4.5/src/Control/Distributed/Process/Tests/CH.hs | |
| 159;21 9: True <- return $ Just ref' == ref && pid == theirAddr && mOrL && reason == reason' | |
| 163;17 9: True <- return $ pid == theirAddr && not mOrL && not un && reason == reason' | |
| 392;11 9: True <- return $ pid' == server2 | |
| 487;13 9: True <- return $ xs == expected | |
| 500;13 9: True <- return $ xs == expected | |
| 544;13 9: True <- return $ xs == "abcacbbacbcacabcba" | |
| 572;9 9: True <- return $ ref == ref' && pid == pid' && ex == show ProcessTerminationException | |
| 587;9 9: True <- return $ ref == ref' && nid == localNodeId node1 | |
| 606;9 9: True <- return $ ref == ref' && nid == localNodeId node1 | |
| 647;9 9: True <- return $ pingServer == pid | |
| 651;9 9: True <- return $ pingServer == pid' | |
| 654;9 9: True <- return $ x == pingServer | |
| 671;9 9: True <- return $ pingServer == pid | |
| 675;9 9: True <- return $ pingServer == pid' | |
| 698;9 9: True <- return $ pingServer == pid | |
| 702;9 9: True <- return $ pingServer == pid' | |
| 739;9 9: True <- return $ pingServer == pid | |
| 743;9 9: True <- return $ pingServer == pid' | |
| 797;9 9: True <- return $ msg1 == "message 1" && msg2 == "message 3" | |
| 893;9 9: True <- return $ isSorted msgs && not (null msgs) | |
| 1202;9 9: True <- return $ ref == ref' && pid == pid' && ex == "killed-by=" ++ show us ++ ",reason=TestKill" | |
| 1221;9 9: True <- return $ ref == ref' && pid == pid' && reason == "killed-by=" ++ show us ++ ",reason=TestKill" | |
| 1295;13 9: True <- return $ reason == ("foobar", 123 :: Int) | |
| 1310;15 9: True <- return $ (show ex) == expected | |
| 1327;13 9: True <- return $ reason == "TestExit" | |
| 1336;9 9: True <- return $ ref == ref' && pid == pid' | |
| 1353;13 9: True <- return $ reason == "TestExit" | |
| 1360;9 9: True <- return $ ref == ref' && pid == pid' | |
| :DPM-0.3.0.0/src/DPM/Core/Darcs.hs | |
| 210;41 9: (repoPatches':\/:bundlePatches') <- return $ findUncommon repoPatches bundlePatches | |
| 244;26 9: conflicts <- return [] | |
| :DrHylo-0.0.2/src/DrHylo.hs | |
| 124;11 9: pw0 <- return (step (replace (d++consts) pw)) | |
| 126;11 9: pw2 <- return (if (name `elem` free pw1) | |
| 129;11 9: pw3 <- return (subst (map (\v -> (v, Pw.Const v)) (free pw2)) pw2) | |
| 130;17 9: (rhs',ob) <- return (if (pwrequired f) | |
| 174;13 9: hsModule0 <- return (casificate hsModule) | |
| 175;13 9: hsModule1 <- return (functorOfInst ob hsModule0) | |
| 176;13 9: hsModule2 <- return (pwpfModule flags (getCtx hsModule1) hsModule1) | |
| :DSH-0.12.0.1/src/Database/DSH/CL/Opt/Auxiliary.hs | |
| 130;9 9: [x'] <- return $ freeVars e1 | |
| 131;9 9: [y'] <- return $ freeVars e2 | |
| 357;29 9: ((g : gs), guards@(_:_)) <- return $ partitionEithers $ map fromQual $ toList qs | |
| :DSH-0.12.0.1/src/Database/DSH/CL/Opt/CompNormalization.hs | |
| 166;29 9: ((g : gs), guards@(_:_)) <- return $ partitionEithers $ map fromQual $ toList qs | |
| :DSH-0.12.0.1/src/Database/DSH/CL/Opt/FlatJoin.hs | |
| 50;63 9: (ExprCL (Comp ty h qs), guardsToTry', leftOverGuards') <- return res | |
| :DSH-0.12.0.1/src/Database/DSH/CL/Opt/NestJoin.hs | |
| 383;27 9: ExprCL (Comp _ h' qs') <- return comp' | |
| :DSH-0.12.0.1/src/Database/DSH/CL/Opt/PartialEval.hs | |
| 30;18 9: TupleT [_, _] <- return tupleTy | |
| :DSH-0.12.0.1/src/Database/DSH/CL/Opt/PredPushdown.hs | |
| 139;53 9: ExprCL (BinOp _ (SBRelOp op) leftExpr rightExpr) <- return $ inject p | |
| 214;9 9: [x'] <- return $ freeVars p | |
| 222;9 9: [x'] <- return $ freeVars p | |
| :DSH-0.12.0.1/src/Database/DSH/VL/Opt/Properties/ReqColumns.hs | |
| 83;24 9: VProp (VTDataVec w) <- return $ vectorTypeProp props | |
| :DSH-0.12.0.1/src/Database/DSH/VL/Opt/Rewrite/Redundant.hs | |
| 468;28 9: VProp card1 <- return $ card1Prop prop1 | |
| 469;28 9: VProp (ConstVec ps) <- return $ constProp prop1 | |
| 472;28 9: VProp card2 <- return $ card1Prop prop2 | |
| 488;28 9: VProp card1 <- return $ card1Prop prop1 | |
| 492;28 9: VProp card2 <- return $ card1Prop prop2 | |
| 493;28 9: VProp (ConstVec ps) <- return $ constProp prop2 | |
| 765;19 9: [predExpr] <- return $(v "predProj") | |
| 766;19 9: [thenExpr] <- return $(v "thenProj") | |
| 767;19 9: [elseExpr] <- return $(v "elseProj") | |
| 1074;53 9: BinApp (SBRelOp op) (Column lc) (Column rc) <- return $(v "p") | |
| :DSH-0.12.0.1/src/Database/DSH/VL/Opt/Rewrite/Window.hs | |
| 47;58 9: SingleJoinPred (Column nrCol) GtE (Column nrCol') <- return $(v "p") | |
| 97;27 9:-- (SBRelOp Eq, 1) <- return $(v "selectArgs") | |
| 102;68 9:-- DoubleJoinPred e11 op1 e12 e21 op2 e22 <- return $(v "joinPred") | |
| 103;68 9:-- (SubExpr (Column nrCol) frameOffset, LtE, Column nrCol') <- return (e11, op1, e12) | |
| 104;68 9:-- (Column nrCol'', GtE, Column nrCol''') <- return (e21, op2, e22) | |
| 105;68 9:-- Constant (IntV offset) <- return frameOffset | |
| :dsh-sql-0.2.0.2/src/Database/DSH/Backend/Sql/Opt/Rewrite/Basic.hs | |
| 104;21 9: (res, _, _) <- return $(v "args") | |
| 117;18 9: (res, _) <- return $(v "args") | |
| 147;26 9: (aggrs, partCols) <- return $(v "args") | |
| 332;26 9: (aggrs, partCols) <- return $(v "args") | |
| 379;29 9: (rcs, kcs, ocs, pcs) <- return $(v "args") | |
| 415;29 9: (rcs, kcs, ocs, pcs) <- return $(v "args") | |
| 445;35 9: (aggrFuns, keyCols@(_:_)) <- return $(v "args") | |
| 476;39 9: (resCol, sortCols, partExprs) <- return $(v "args") | |
| 489;28 9: (resCol, sortCols) <- return $(v "args") | |
| 501;47 9:-- (mDescr, RelPos sortCols, payload) <- return $(v "args") | |
| 545;44 9: (resCol, sortCols@(_:_), groupCols) <- return $(v "o") | |
| 568;35 9:-- (d, RelPos cs, reqCols) <- return $(v "scols") | |
| 612;31 9: (resCol, sortCols, []) <- return $(v "args") | |
| 620;20 9: Just prefix <- return $ find (isKeyPrefix keys) ordPrefixes | |
| 631;31 9: (resCol, sortCols, []) <- return $(v "args") | |
| 661;46 9:-- (mDescr, RelPos sortCols, payload) <- return $(v "args") | |
| 697;29 9:-- (d, p, reqCols) <- return $(v "scols") | |
| 822;49 9: ((resCol, f), [], sortSpec, frameSpec) <- return $(v "args") | |
| :dwarf-0.23/src/Data/Dwarf.hs | |
| 117;13 9: temp <- return $ acc .|. (clearBit byte 7 `shiftL` shift) | |
| 132;13 9: temp <- return $ acc .|. (clearBit byte 7 `shiftL` shift) | |
| 285;24 9: dr <- return $ case addr_size of | |
| 342;26 9: dr <- return $ dwarfReader target64 dr | |
| 369;26 9: dr <- return $ dwarfReader target64 dr | |
| 543;31 9: dr <- return $ dwarfReader target64 dr | |
| 676;17 9: dr <- return $ dwarfEndianReader littleEndian | |
| 678;17 9: dr <- return $ dwarfReader target64 dr | |
| 692;32 9: initial_instructions <- return $ runGet (getWhileNotEmpty (getDW_CFA dr)) $ L.fromChunks [raw_instructions] | |
| 699;32 9: instructions <- return $ runGet (getWhileNotEmpty (getDW_CFA dr)) $ L.fromChunks [raw_instructions] | |
| :dx9base-0.1.1/gen/Parser.hs | |
| 350;60 9: peek p = [" " ++ p ++ " <- peekByteOff b 0\n"," b <- return $ plusPtr b (sizeOf " ++ p ++ ")\n"] | |
| :dx9d3d-0.1.1.1/DirectX9/D3D/Raw.hs | |
| 21;10 9: b <- return $ plusPtr b (sizeOf p1) | |
| 23;10 9: b <- return $ plusPtr b (sizeOf p1) | |
| 25;10 9: b <- return $ plusPtr b (sizeOf p1) | |
| 48;10 9: b <- return $ plusPtr b (sizeOf p1) | |
| 50;10 9: b <- return $ plusPtr b (sizeOf p1) | |
| 52;10 9: b <- return $ plusPtr b (sizeOf p1) | |
| 54;10 9: b <- return $ plusPtr b (sizeOf p1) | |
| 56;10 9: b <- return $ plusPtr b (sizeOf p1) | |
| 58;10 9: b <- return $ plusPtr b (sizeOf p1) | |
| 60;10 9: b <- return $ plusPtr b (sizeOf p1) | |
| 62;10 9: b <- return $ plusPtr b (sizeOf p1) | |
| 64;10 9: b <- return $ plusPtr b (sizeOf p1) | |
| 66;10 9: b <- return $ plusPtr b (sizeOf p1) | |
| 68;10 9: b <- return $ plusPtr b (sizeOf p1) | |
| 70;10 9: b <- return $ plusPtr b (sizeOf p1) | |
| 72;10 9: b <- return $ plusPtr b (sizeOf p1) | |
| 74;10 9: b <- return $ plusPtr b (sizeOf p1) | |
| 76;10 9: b <- return $ plusPtr b (sizeOf p1) | |
| :dx9d3d-0.1.1.1/gen/Parser.hs | |
| 350;60 9: peek p = [" " ++ p ++ " <- peekByteOff b 0\n"," b <- return $ plusPtr b (sizeOf " ++ p ++ ")\n"] | |
| :dx9d3dx-0.1.1/gen/Parser.hs | |
| 350;60 9: peek p = [" " ++ p ++ " <- peekByteOff b 0\n"," b <- return $ plusPtr b (sizeOf " ++ p ++ ")\n"] | |
| :edit-lenses-demo-0.1/Data/Module/String.hs | |
| 133;20 9: ("", sMatch, rest) <- return (s =~ re) | |
| :effect-monad-0.6.1/examples/Counter.hs | |
| 21;11 9:foo = do x <- return 2 | |
| 22;11 9: y <- return 4 | |
| 29;12 9: y <- return 3 | |
| :effect-monad-0.6.1/examples/CounterNat.hs | |
| 21;11 9:foo = do x <- return 2 | |
| 22;11 9: y <- return 4 | |
| 29;12 9: y <- return 3 | |
| :egison-3.6.0/hs-src/Language/Egison/Desugar.hs | |
| 57;13 9: matcherRef <- return $ VarExpr matcherName | |
| 66;16 9: clauses <- return $ [main] ++ body ++ [footer] | |
| :egison-3.6.0/hs-src/Language/Egison/Core.hs | |
| 890;23 9: keys <- return $ HL.keys hash | |
| :egison-3.6.0/hs-src/Language/Egison/Types.hs | |
| 1119;10 9: (a, s') <- return $ runFresh s m | |
| :elf-0.27/src/Data/Elf.hs | |
| 457;16 9: er <- return $ elfReader ei_data | |
| :Encode-1.3.8/Encode/Arabic/ArabTeX/ZDMG.hs | |
| 272;22 9: v <- return "" -- oneof [sukun] | |
| :esotericbot-0.0.6/Esotericbot/IRCCom.hs | |
| 103;7 9: msg <- return $ cmd `hAppend` singleton ' ' `hAppend` val | |
| 126;7 9: msg <- return $ priv_msg `hAppend` c `hAppend` colon `hAppend` m | |
| :explore-0.0.7.2/Main.hs | |
| 161;14 9: matching <- return . read $ matching_ | |
| 162;14 9: area <- return . read $ area_ | |
| 167;14 9: stepSize <- return $ case step_ of | |
| 170;14 9: translation <- return $ case null oargs of | |
| :external-sort-0.2/src/Algorithms/ExternalSort.lhs | |
| 161;16 9:> (res :: Int) <- return . last =<< externalSort bigList | |
| :extra-1.4.8/Generate.hs | |
| 20;9 9: mods <- return $ filter (isSuffixOf ".Extra") $ map trim $ lines src | |
| :Extra-1.46.3/Extra/HughesPJ.hs | |
| 10;15 9: do columns <- return . fromMaybe 80 =<< getWidth | |
| :ez-couch-0.7.0/src/EZCouch/EntityIsolation.hs | |
| 59;10 9: results <- return | |
| :ez-couch-0.7.0/src/Util/Logging.hs | |
| 30;4 9: h <- return $ setFormatter h (formatter format) | |
| :fast-tags-1.2/src/Main.hs | |
| 107;20 9: newTags <- return $ if noModuleTags | |
| :fay-0.23.1.12/src/haskell-names/Language/Haskell/Names/Exports.hs | |
| 83;24 9: , Just n' <- return $ sv_parent info | |
| :fay-0.23.1.12/src/haskell-names/Language/Haskell/Names/GetBound.hs | |
| 87;24 9: | Just fieldDecls <- return mbFieldDecls | |
| :fay-0.23.1.12/src/haskell-names/Language/Haskell/Names/Imports.hs | |
| 206;20 9: , Just n' <- return $ sv_parent info | |
| :fay-0.23.1.12/src/haskell-names/Language/Haskell/Names/ScopeUtils.hs | |
| 71;15 9: , Just p <- return $ sv_parent info | |
| :fay-0.23.1.12/tests/doAssingPatternMatch.hs | |
| 5;8 9: [1,2] <- return [1,2] | |
| :fay-0.23.1.12/tests/doBindAssign.hs | |
| 5;4 9: x <- return "Hello, World!" >>= return | |
| :fay-0.23.1.12/tests/doLet.hs | |
| 18;4 9: x <- return 10 | |
| 22;4 9: x <- return 123 | |
| 27;4 9: x <- return 123 | |
| 34;4 9: x <- return 123 | |
| 42;9 9: Just x <- return (Just 123) | |
| 51;6 9: I i <- return (I 1) | |
| :fay-0.23.1.12/tests/Monad.hs | |
| 6;6 9: 123 <- return 123 | |
| 7;4 9: x <- return 456 | |
| 9;4 9: x <- return 666 >>= \_ -> return 789 | |
| 10;4 9: y <- return 101112 | |
| :fb-1.0.13/tests/Main.hs | |
| 148;39 9: Just testUserAccessTokenData <- return (FB.tuAccessToken testUser) | |
| :feed2lj-0.0.3.1/Feed2Lj.hs | |
| 121;9 9: ljuser <- return fromJust `ap` readLjSetting "username" | |
| 122;9 9: ljpass <- return fromJust `ap` readLjSetting "password" | |
| 123;11 9: sentfile <- return fromJust `ap` readLjSetting "sentfile" | |
| 124;4 9: t <- return fromJust `ap` readLjSetting "template" | |
| 125;13 9: nsentences <- return readMaybeInt `ap` readLjSetting "nsentences" | |
| :FermatsLastMargin-0.1/FLM/Control.hs | |
| 14;20 9:createPage = do pid <- return . abs =<< randomIO | |
| :ffeed-0.3.2/FriendFeed/Types/Import.hs | |
| 158;8 9: cs <- return [] | |
| 160;8 9: ms <- return [] | |
| 162;10 9:-- likes <- return [] | |
| :firstify-0.1/Firstify.hs | |
| 60;9 9: errs <- return $ ["No file specified" | null files] ++ | |
| 71;6 9: c <- return $ if null newmain then c else replaceMain c (head newmain) | |
| 112;6 9: c <- return $ if Normalise `notElem` acts then c else | |
| :firstify-0.1/Yhc/Core/Firstify/Mitchell.hs | |
| 213;20 9: (c,(new,s)) <- return $ flip runState (Map.empty,s) $ | |
| :firstify-0.1/Yhc/Core/Firstify/MitchellOld.hs | |
| 180;20 9: (c,(new,s)) <- return $ runState (applyFuncCoreM f c) ([],s) | |
| :firstify-0.1/Yhc/Core/Firstify/Super.hs | |
| 48;10 9: c <- return $ ensureInvariants [NoRecursiveLet,NoCorePos] c | |
| 59;9 9: func <- return $ coreFuncMap (core s) x | |
| 96;7 9: xs <- return $ xs ++ map CoreVar vs | |
| 97;6 9: o <- return $ CoreApp (CoreFun x) xs | |
| 273;20 9: (c,(new,s)) <- return $ flip runState (Map.empty,s) $ | |
| :fix-imports-1.0.4/src/FixImports.hs | |
| 80;11 9: config <- return $ config | |
| :Flippi-0.0.5/src/Flippi.hs | |
| 50;15 9:cgi env = do m <- return (maybe "GET" id (lookup "REQUEST_METHOD" env)) | |
| 51;16 9: qs <- return (maybe "" id (lookup "QUERY_STRING" env)) | |
| 71;29 9:handleGet qs env = do action <- return (parseParms qs) | |
| 83;30 9:handlePost qs env = do action <- return (parseParms qs) | |
| 95;27 9:updatePage p env = do text <- return (lookup "Text" env) | |
| 96;34 9: oldmodified <- return (lookup "oldDate" env) | |
| :Flippi-0.0.5/src/PageIO.hs | |
| 85;34 9: c2 <- return (isPagename fp) | |
| :Flippi-0.0.5/src/PageTemplates.hs | |
| 63;21 9:page p t env = do sn <- return (maybe "" id (lookup "SCRIPT_NAME" env)) | |
| 77;23 9:editPage p env = do sn <- return (maybe "" id (lookup "SCRIPT_NAME" env)) | |
| 109;27 9:pageNotFound p env = do sn <- return (maybe "" id (lookup "SCRIPT_NAME" env)) | |
| :Flippi-0.0.5/src/RecentChanges.hs | |
| 39;28 9: pnds <- return $ filter (\(_,md) -> | |
| 45;29 9: opnds <- return $ sortBy ordering pnds | |
| 51;27 9: out <- return $ | |
| :fltkhs-0.4.0.7/src/Fluid/Generate.hs | |
| 397;25 9: newName <- return (haskellIdToName takenNames hsClassName haskellId) | |
| :formal-0.1.0/src/hs/Formal/TypeCheck/Types.hs | |
| 261;28 9: do (_ :=> t') <- return$ inst (map TypeVar$ tv t) x | |
| :formal-0.1.0/src/hs/Formal/TypeCheck.hs | |
| 137;34 9: (qs :=> t''') <- return$ inst (map TypeVar$ tv t'') (scr) | |
| :formal-0.1.0/src/hs/Formal/Types/Pattern.hs | |
| 239;34 9: (qs :=> t''') <- return$ inst (map TypeVar$ tv t'') scr | |
| :forml-0.2/src/hs/Forml/TypeCheck/Types.hs | |
| 281;25 9: t''' <- return$ inst (map TypeVar$ tv t'') scr | |
| 402;29 9: do t' <- return$ inst (map TypeVar$ tv t) x | |
| :forml-0.2/src/hs/Forml/TypeCheck.hs | |
| 155;25 9: t''' <- return$ inst (map TypeVar$ tv t'') (scr) | |
| :forml-0.2/src/hs/Forml/Types/Pattern.hs | |
| 250;25 9: t''' <- return$ inst (map TypeVar$ tv t'') scr | |
| :formura-1.0/src/Formura/Cxx/Translate.hs | |
| 88;30 9: Just (VariableName vn) <- return $ A.viewMaybe nd | |
| 141;36 9: Just (VariableName newName) <- return $ A.viewMaybe n | |
| :Fractaler-3/Fractaler.hs | |
| 66;5 9: rnd <- return $ null args | |
| 254;5 9: mid <- return $ truncate $ (y/16)+(if x<196 then 0 else 32) | |
| 267;4 9: tw <- return $ truncate w | |
| 273;8 9: colors <- return $ concat $ map (\(r,g,b) -> map double2Float [r,g,b]) $ withStrategy (parBuffer 512 rseq) . map (func vc) $ pts xy w | |
| :frag-1.1.2/src/BSP.hs | |
| 380;15 9: startVIndex <- return (startVertIndex face) | |
| 658;21 9: texFileNames <- return (map strName texInfos) | |
| 919;7 9: ptr <- return (advancePtr lightMap (3*offst)) | |
| 924;10 9: byter2 <- return $ fromIntegral $ (truncate (r2 * tempb * 255.0) :: Int) | |
| 925;10 9: byteg2 <- return $ fromIntegral $ (truncate (g2 * tempb * 255.0) :: Int) | |
| 926;10 9: byteb2 <- return $ fromIntegral $ (truncate (b2 * tempb * 255.0) :: Int) | |
| :frag-1.1.2/src/Textures.hs | |
| 19;17 9: fileNamesExts <- return (map (("tga/" ++) . (++ ".tga")) fileNames) | |
| :franchise-0.0.6/Distribution/Franchise/Darcs.hs | |
| 55;32 9: ((patches'',_):_) <- return $ reads patches' | |
| 69;35 9: ((_:zzz:_):_) <- return $ filter ("tagged" `elem`) $ | |
| :frown-0.6.2.3/Lexer.lhs | |
| 194;39 9:> | e `elem` "eE" = do (c : t) <- return s | |
| 203;39 9:> lexDigits' s = do (cs@(_ : _), t) <- return (span isDigit s) | |
| :frown-0.6.2.3/Lexer2.lhs | |
| 121;39 9:> | e `elem` "eE" = do (c : t) <- return s | |
| 130;39 9:> lexDigits' s = do (cs@(_ : _), t) <- return (span isDigit s) | |
| :funsat-0.6.2/tests/Properties.hs | |
| 271;10 9: do is <- return [x..] | |
| :genifunctors-0.3/Data/Generics/Genifunctors.hs | |
| 340;13 9: '(' : s1 <- return s | |
| 341;18 9: (commas, ")") <- return $ span (== ',') s1 | |
| :getemx-0.1/Emx/Dl.hs | |
| 31;13 9: (key, val) <- return $ parseHeader $ map toLower s | |
| :getemx-0.1/Emx/Options.hs | |
| 31;21 9: (kind, rest) <- return $ break (==')') cs | |
| :gf-3.7.1/src/example-based/ExampleService.hs | |
| 52;14 9: Just abs <- return $ readExpr absstr | |
| 68;14 9: Just txt <- return (E.testThis environ fun parsePGF lang) | |
| :gf-3.7.1/src/server/exec/MorphoService.hs | |
| 54;39 9: "/eval" -> do mjson <- return (doEval sgr) `ap` getTerm | |
| :ghc-exactprint-0.5.0.1/tests/examples/ghc710/Arrows.hs | |
| 20;5 9: y <- return (2 * x) | |
| 21;5 9: z1 <- return (y + 3) | |
| 22;5 9: z2 <- return (y - 5) | |
| :ghc-exactprint-0.5.0.1/tests/examples/ghc8/ado003.hs | |
| 7;6 9: 'a' <- return (3::Int) -- type error | |
| :ghc-exactprint-0.5.0.1/tests/examples/ghc8/ado006.hs | |
| 8;8 9: x <- return () | |
| 9;8 9: h <- return (\_ -> 3) | |
| :ghc-exactprint-0.5.0.1/tests/examples/ghc8/ado007.hs | |
| 13;4 9: x <- return 'a' | |
| 14;4 9: y <- return 'b' | |
| :ghc-exactprint-0.5.0.1/tests/examples/ghc8/T9973.hs | |
| 8;16 9: = do { newSpan <- return typeSig | |
| :ghc-make-0.3.2/src/Arguments.hs | |
| 95;6 9: x <- return $ fromMaybe x $ stripPrefix "=" x | |
| 96;13 9: [(i,"")] <- return $ reads x | |
| :ghc-make-0.3.2/src/Main.hs | |
| 48;17 9: needArgs <- return $ do need [prefix <.> "args"]; return argsGHC | |
| 55;17 9: needPkgs <- return $ need [prefix <.> "pkgs"] | |
| :ghc-mod-5.5.0.0/test/MonadSpec.hs | |
| 16;32 9: Just _ <- return Nothing | |
| :ghcid-0.6.4/src/Ghcid.hs | |
| 130;15 9: height <- return $ case (width, height) of | |
| 159;17 9: load <- return $ take (if isJust load then n else 0) $ prettyOutput (maybe 0 fst load) | |
| 176;17 9: test <- return $ if countErrors == 0 && (warnings || countWarnings == 0) then test else Nothing | |
| :ghcid-0.6.4/src/Language/Haskell/Ghcid/Terminal.hs | |
| 54;8 9: ico <- return $ case x of | |
| :ghcid-0.6.4/src/Language/Haskell/Ghcid.hs | |
| 146;14 9: s <- return $ maybe s (removePrefix . snd) $ stripInfix ghcid_prefix s | |
| :ghcid-0.6.4/src/Session.hs | |
| 73;13 9: messages <- return $ mapMaybe tidyMessage messages | |
| 107;17 9: messages <- return $ messages ++ filter validWarn warn | |
| :ghcid-0.6.4/src/Test/Polling.hs | |
| 98;14 9: writeFile <- return $ \name x -> do print ("writeFile",name,x); writeFile name x | |
| 99;15 9: renameFile <- return $ \from to -> do print ("renameFile",from,to); renameFile from to | |
| :ginsu-0.8.2.1/Gale/Gale.hs | |
| 98;7 9: ps <- return (case ps of [] -> snub (concatMap (hostStrings . categoryCell) ncs); _ -> ps) | |
| :ginsu-0.8.2.1/KeyName.hs | |
| 120;42 9: let fl = concatMap ((\x -> do (a:b:_) <- return x ; return (a,b)) . words) cl | |
| :ginsu-0.8.2.1/Main.hs | |
| 491;28 9: (it,is,notIdle) <- return $ case ct - uat of | |
| 986;13 9: body <- return $ if not tw then (unlines $ (drop 2 pn)) else | |
| 1021;9 9: puff <- return $ puff {cats = ncats} | |
| :gipeda-0.3/src/ParentMap.hs | |
| 22;10 9: , p:_ <- return parents | |
| :gipeda-0.3/src/Shake.hs | |
| 306;35 9: need [resultsOf h | Just h <- return pred] | |
| 308;60 9: Stdout json <- self "RevReport" (hash : [h | Just h <- return pred]) | |
| :git-annex-6.20160527/Build/EvilSplicer.hs | |
| 614;43 9: - Fix by converting the "let x = " to "x <- return $" | |
| 621;31 9: return $ "= do { " ++ x ++ " <- return $ " | |
| :gitit-0.12.1.1/src/Network/Gitit.hs | |
| 52;9 9:> user <- return "testuser" | |
| :glome-hs-0.61/Glome.hs | |
| 223;34 9: (scene,s) <- return $ Prelude.head $ reads filestring | |
| :goatee-gtk-0.3.1/src/Game/Goatee/Ui/Gtk/Goban.hs | |
| 345;30 9: (canvasWidth, canvasHeight) <- return . mapTuple fromIntegral =<< widgetGetSize drawingArea | |
| :gpah-0.0.2/src/Generics/GPAH/Main.hs | |
| 105;14 9: haskellSrcs <- return . concat . zipWith (\ abssrcdir srcs -> zip (repeat abssrcdir) srcs) pkgAbsSrcDirs =<< mapM getHaskellSrcs pkgAbsSrcDirs | |
| :gpah-0.0.2/src/Generics/GPAH/Utils.hs | |
| 163;11 10: contents <- return . B.unpack =<< B.hGetContents h | |
| :GPipe-Collada-0.1.4/src/Graphics/GPipe/Collada/Parse.hs | |
| 170;120 9: xs <- withError "Expecting COLLADA top-element" $ do XML.Document _ _ (Elem (N "COLLADA") _ xs) _ <- return p | |
| 191;138 9: Just lurl -> do assert $ \refmap -> withError (missingLinkErr "visual_scene" lurl c) $ do Just (RefVisualScene _) <- return $ getRef lurl refmap | |
| 230;126 9: assert $ \refmap -> do m <- withError (missingLinkErr "*_array" id acc) $ do Just (RefArray m) <- return $ getRef id refmap | |
| 262;132 9: Just id -> do assert $ \refmap -> withError (missingLinkErr "instance_node" id c) $ do Just (RefNode _) <- return $ getRef id refmap | |
| 271;141 9: Just id -> do assert $ \ refmap -> withError (missingLinkErr "instance_camera" id c) $ do Just (RefCamera _) <- return $ getRef id refmap | |
| 278;139 9: Just id -> do assert $ \ refmap -> withError (missingLinkErr "instance_light" id c) $ do Just (RefLight _) <- return $ getRef id refmap | |
| 285;143 9: Just id -> do assert $ \ refmap -> withError (missingLinkErr "instance_camera" id c) $ do Just (RefGeometry _) <- return $ getRef id refmap | |
| :guarded-rewriting-0.1/performance/Common/DNF.hs | |
| 55;6 9: xs <- return (r a) | |
| :hacanon-light-2008.10.28/src/Foreign/HacanonLight/DIS/Types.hs | |
| 27;68 9: unmarshal2 <- return t2 | |
| :hackage-server-0.5.0/Distribution/Server/Packages/Index.hs | |
| 60;22 9: Right tarPath <- return $ Tar.toTarPath False path | |
| :hackport-0.5/cabal/cabal-install/Distribution/Client/FileMonitor.hs | |
| 681;16 9: matches <- return . filter (matchGlob glob) | |
| :hackport-0.5/cabal/cabal-install/Distribution/Client/Init.hs | |
| 181;11 13: pkgName' <- return (flagToMaybe $ packageName flags) | |
| 206;5 13: v' <- return (flagToMaybe $ version flags) | |
| 214;6 13: lic <- return (flagToMaybe $ license flags) | |
| 230;15 13: authorName' <- return (flagToMaybe $ author flags) | |
| 234;15 13: authorEmail' <- return (flagToMaybe $ email flags) | |
| 246;6 13: hp' <- return (flagToMaybe $ homepage flags) | |
| 260;6 13: syn <- return (flagToMaybe $ synopsis flags) | |
| 270;6 13: cat <- return (flagToMaybe $ category flags) | |
| 278;16 13: extraSrcFiles <- return (extraSrc flags) | |
| 309;8 13: isLib <- return (flagToMaybe $ packageType flags) | |
| 341;7 13: lang <- return (flagToMaybe $ language flags) | |
| 354;14 13: genComments <- return (not <$> flagToMaybe (noComments flags)) | |
| 364;10 9: srcDirs <- return (sourceDirs flags) | |
| 391;12 14: Just mods <- return (exposedModules flags) | |
| 394;8 13: tools <- return (buildTools flags) | |
| 397;7 14: deps <- return (dependencies flags) | |
| 409;7 13: exts <- return (otherExts flags) | |
| :hackport-0.5/Merge/Dependencies.hs | |
| 374;8 9: , pkg <- return (lookup pn buildToolsTable) | |
| :hackport-0.5/Portage/GHCCore.hs | |
| 93;47 9: , Right (pkg_desc, picked_flags) <- return (packageBuildableWithGHCVersion gpd user_specified_fas g)] | |
| :haddock-leksah-2.6.0/src/Haddock/InterfaceFile.hs | |
| 104;5 9: bh <- return $ setUserData bh0 ud | |
| 186;10 9: bh2 <- return $! setUserData bh1 ud'{ud_symtab = symtab} | |
| :halipeto-2.4.1/Halipeto/Pages.lhs | |
| 290;19 9: p'' <- return $ p' `slash` s | |
| :halipeto-2.4.1/Halipeto/SimpleDB.lhs | |
| 176;20 9: txt' <- return $ dropWindowsReturn txt | |
| :hamid-0.10/src/System/MacOSX/CoreMidi.hs | |
| 454;36 9: poke (castPtr p) ep ; r <- return (p `plusPtr` ptrsize) | |
| 455;36 9: poke (castPtr r) q ; r <- return (r `plusPtr` ptrsize) | |
| 456;36 9: poke (castPtr r) n ; r <- return (r `plusPtr` 4 ) | |
| 457;36 9: poke (castPtr r) (0::Int32) ; r <- return (r `plusPtr` 4 ) | |
| 458;36 9: poke (castPtr r) cb ; r <- return (r `plusPtr` ptrsize) | |
| :hamid-0.10/src/System/Win32/Midi.hs | |
| 186;34 9: mid <- peek (castPtr p) ; q <- return (p `plusPtr` 2) | |
| 187;34 9: pid <- peek (castPtr q) ; q <- return (q `plusPtr` 2) | |
| 188;34 9: ver <- peek (castPtr q) ; q <- return (q `plusPtr` 4) | |
| 189;41 9: nam <- peekTString (castPtr q) ; q <- return (q `plusPtr` (4*maxPNAMELEN)) | |
| 210;34 9: mid <- peek (castPtr p) ; q <- return (p `plusPtr` 2) | |
| 211;34 9: pid <- peek (castPtr q) ; q <- return (q `plusPtr` 2) | |
| 212;34 9: ver <- peek (castPtr q) ; q <- return (q `plusPtr` 4) | |
| 213;41 9: nam <- peekTString (castPtr q) ; q <- return (q `plusPtr` (4*maxPNAMELEN)) | |
| 214;34 9: tec <- peek (castPtr p) ; q <- return (p `plusPtr` 2) | |
| 215;34 9: voi <- peek (castPtr p) ; q <- return (p `plusPtr` 2) | |
| 216;34 9: not <- peek (castPtr p) ; q <- return (p `plusPtr` 2) | |
| 217;34 9: chm <- peek (castPtr p) ; q <- return (p `plusPtr` 2) | |
| :hangman-1.0.3/src/main/haskell/Main.hs | |
| 104;18 9: (randomIndex,_) <- return . randomR (0,length listOfWords) =<< newStdGen | |
| :hannahci-0.1.4.2/Control/HannahCI/Handler.hs | |
| 41;7 9: hook <- return $ parseHook body | |
| 46;12 9: repos <- return $ filterRepos info hook | |
| :hannahci-0.1.4.2/System/Posix/IO/Log.hs | |
| 29;14 9: dir <- return $ getLogPath info | |
| 35;14 9: latest <- return $ maximum files | |
| 50;11 9: logPath <- return $ getLogPath info | |
| :HAppS-IxSet-0.9.3/src/HAppS/Data/IxSet.hs | |
| 229;25 9: --d <- return $ deriveDefault' True [aType] ''IxSet | |
| :happs-tutorial-0.9.5/src/ControllerGetActions.hs | |
| 46;20 9: consultantswanted <- return . map unusername . M.keys | |
| :happs-tutorial-0.9.5/src/ControllerStressTests.hs | |
| 57;11 9: us <- return . M.toList . users =<< query AskDatastore | |
| :happs-tutorial-0.9.5/src/FromDataInstances.hs | |
| 85;17 9:lookjob = do bud <- return . B.pack =<< (look "jobbudget" `mplus` return "") | |
| 86;22 9: jobBlurb <- return . B.pack =<< (look "jobdescription" `mplus` return "") | |
| :happs-tutorial-0.9.5/src/UniqueLabelsGraph.hs | |
| 68;11 9: oldgraph <- return . snd =<< get -- couldn't we just say: g instead of oldgraph and skip this? | |
| :happstack-facebook-0.30/Happstack/Facebook/Application.hs | |
| 283;11 9: req <- return $ buildRequest configData params | |
| 293;11 9: req <- return $ buildRequest configData params | |
| :happstack-facebook-0.30/Happstack/Facebook/Common.hs | |
| 292;11 9: req <- return $ buildRequest configData params | |
| 301;11 9: req <- return $ buildRequest configData params | |
| 311;11 9: req <- return $ buildRequest configData params | |
| :hashabler-1.2.1/src/Data/Hashabler/SipHash.hs | |
| 41;7 9: v0 <- return $ v0 + v1 | |
| 42;7 9: v1 <- return $ rotl v1 13 | |
| 43;7 9: v1 <- return $ v1 `xor` v0 | |
| 44;7 9: v0 <- return $ rotl v0 32 | |
| 46;7 9: v2 <- return $ v2 + v3 | |
| 47;7 9: v3 <- return $ rotl v3 16 | |
| 48;7 9: v3 <- return $ v3 `xor` v2 | |
| 50;7 9: v0 <- return $ v0 + v3 | |
| 51;7 9: v3 <- return $ rotl v3 21 | |
| 52;7 9: v3 <- return $ v3 `xor` v0 | |
| 54;7 9: v2 <- return $ v2 + v1 | |
| 55;7 9: v1 <- return $ rotl v1 17 | |
| 56;7 9: v1 <- return $ v1 `xor` v2 | |
| 57;7 9: v2 <- return $ rotl v2 32 | |
| 109;33 9: bytesRemaining <- return $ bytesRemaining - mSize | |
| 110;24 9: inlen <- return $ inlen + mSize | |
| 118;24 9: inlen <- return $ inlen + mSize | |
| 129;24 9: inlen <- return $ inlen + mSize | |
| 137;24 9: inlen <- return $ inlen + mSize | |
| 157;11 9: v3 <- return $ v3 `xor` m | |
| 159;22 9: (v0,v1,v2,v3) <- return $ sipRound v0 v1 v2 v3 | |
| 160;22 9: (v0,v1,v2,v3) <- return $ sipRound v0 v1 v2 v3 | |
| 162;11 9: v0 <- return $ v0 `xor` m | |
| 178;7 9: v3 <- return $ v3 `xor` k1; | |
| 179;7 9: v2 <- return $ v2 `xor` k0; | |
| 180;7 9: v1 <- return $ v1 `xor` k1; | |
| 181;7 9: v0 <- return $ v0 `xor` k0; | |
| 187;19 9: SipState{ .. } <- return $ hash (SipState { .. }) a | |
| 190;6 9: b <- return $ b .|. mPart | |
| 192;7 9: v3 <- return $ v3 `xor` b | |
| 194;18 9: (v0,v1,v2,v3) <- return $ sipRound v0 v1 v2 v3 | |
| 195;18 9: (v0,v1,v2,v3) <- return $ sipRound v0 v1 v2 v3 | |
| 196;7 9: v0 <- return $ v0 `xor` b | |
| 199;7 9: v2 <- return $ v2 `xor` 0xff | |
| 202;18 9: (v0,v1,v2,v3) <- return $ sipRound v0 v1 v2 v3 | |
| 203;18 9: (v0,v1,v2,v3) <- return $ sipRound v0 v1 v2 v3 | |
| 204;18 9: (v0,v1,v2,v3) <- return $ sipRound v0 v1 v2 v3 | |
| 205;18 9: (v0,v1,v2,v3) <- return $ sipRound v0 v1 v2 v3 | |
| 226;7 9: v3 <- return $ v3 `xor` k1; | |
| 227;7 9: v2 <- return $ v2 `xor` k0; | |
| 228;7 9: v1 <- return $ v1 `xor` k1; | |
| 229;7 9: v0 <- return $ v0 `xor` k0; | |
| 232;7 9: v1 <- return $ v1 `xor` 0xee | |
| 238;19 9: SipState{ .. } <- return $ hash (SipState { .. }) a | |
| 241;6 9: b <- return $ b .|. mPart | |
| 243;7 9: v3 <- return $ v3 `xor` b | |
| 245;18 9: (v0,v1,v2,v3) <- return $ sipRound v0 v1 v2 v3 | |
| 246;18 9: (v0,v1,v2,v3) <- return $ sipRound v0 v1 v2 v3 | |
| 247;7 9: v0 <- return $ v0 `xor` b | |
| 251;7 9: v2 <- return $ v2 `xor` 0xee | |
| 254;18 9: (v0,v1,v2,v3) <- return $ sipRound v0 v1 v2 v3 | |
| 255;18 9: (v0,v1,v2,v3) <- return $ sipRound v0 v1 v2 v3 | |
| 256;18 9: (v0,v1,v2,v3) <- return $ sipRound v0 v1 v2 v3 | |
| 257;18 9: (v0,v1,v2,v3) <- return $ sipRound v0 v1 v2 v3 | |
| 262;7 9: v1 <- return $ v1 `xor` 0xdd | |
| 264;18 9: (v0,v1,v2,v3) <- return $ sipRound v0 v1 v2 v3 | |
| 265;18 9: (v0,v1,v2,v3) <- return $ sipRound v0 v1 v2 v3 | |
| 266;18 9: (v0,v1,v2,v3) <- return $ sipRound v0 v1 v2 v3 | |
| 267;18 9: (v0,v1,v2,v3) <- return $ sipRound v0 v1 v2 v3 | |
| :haskbot-core-0.1/src/Network/Haskbot/Internal/Environment.hs | |
| 39;14 9: config <- return configuration | |
| :haskell-cnc-0.1.3.200/examples/primes.hs | |
| 77;14 9: do x <- return $ runGraph $ primes n | |
| :haskell-cnc-0.1.3.200/examples/primes2.hs | |
| 75;14 9: do x <- return $ runGraph $ primes n | |
| :haskell-cnc-0.1.3.200/Intel/CncPure.hs | |
| 496;16 9: len <- return $ length bsteps | |
| :haskell-names-0.6.0/src/Language/Haskell/Names/Annotated.hs | |
| 81;49 9: Scoped (GlobalSymbol symbol _) _ <- return (lookupValue qn sc) | |
| :haskell-names-0.6.0/src/Language/Haskell/Names/Exports.hs | |
| 51;20 9: Just n' <- return $ symbolParent symbol | |
| 115;22 9: Just n' <- return $ symbolParent symbol | |
| :haskell-names-0.6.0/src/Language/Haskell/Names/GetBound.hs | |
| 84;24 9: | Just fieldDecls <- return mbFieldDecls | |
| :haskell-names-0.6.0/src/Language/Haskell/Names/Imports.hs | |
| 197;20 9: , Just n' <- return $ symbolParent symbol | |
| :haskell-names-0.6.0/src/Language/Haskell/Names/ScopeUtils.hs | |
| 64;15 9: Just p <- return $ symbolParent symbol | |
| :haskell-pdf-presenter-0.2.5/HaskellPdfPresenter.hs | |
| 163;8 9: state <- return State | |
| 874;29 9: [Just h, Just m, Just s] <- return $ map (maybeRead . reverse) [hr, mn, sc] | |
| :HaskellTorrent-0.1.1/src/Process/ChokeMgr.hs | |
| 252;16 9: rts <- return $ map (\(pid, pi) -> | |
| :haskore-0.2.0.8/src/Haskore/Interface/AutoTrack/ChordSymbol.lhs | |
| 53;11 9:> b <- return r ReadP.+++ | |
| :hat-2.9.0.0/tools/BlackHat.hs | |
| 23;13 9: hatfile <- return (rectify hatname) | |
| :hat-2.9.0.0/tools/HatNonTerm.hs | |
| 28;13 9: hatfile <- return (rectify hatname) | |
| :Hayoo-1.2.3/src/Hayoo/Search/Parser.hs | |
| 137;13 9: s <- return (stripSignature r) | |
| 138;13 9: n <- return (normalizeSignature r) | |
| :Hayoo-1.2.3/src/Hayoo/Snap/Extension/HayooState.hs | |
| 109;9 9: prnk <- return $ buildRankTable pdoc | |
| 112;9 9: tpl <- return $ makeTemplate (sizeDocs pdoc) (sizeDocs doc) | |
| :Hayoo-1.2.3/src/HayooSnap.hs | |
| 375;14 9: prnk <- return $ buildRankTable pdoc | |
| 378;14 9: tpl <- return $ makeTemplate (sizeDocs pdoc) (sizeDocs doc) | |
| :hblas-0.3.2.1/src/Numerical/HBLAS/BLAS/Internal.hs | |
| 139;34 9: do (axNew,_) <- return $ coordSwapper tra (ax,ay) | |
| :HDBC-mysql-0.6.6.1/Setup.lhs | |
| 41;14 9: includeDirs <- return . map (drop 2) . split ws =<< mysqlConfig ["--include"] | |
| 42;14 9: ldOptions <- return . split ws =<< mysqlConfig ["--libs"] | |
| :hdirect-0.21.0/comlib/TypeLib.hs | |
| 161;8 9: tag <- return (read_tag) | |
| 241;13 9: rgbounds <- return pf3 | |
| 1021;8 9: tag <- return (read_tag) | |
| :hdm-0.0.1/hdm.lhs | |
| 172;11 9:> sessions <- return $ filter (\x -> not (((x == ".") || (x == "..")) || (x == "current"))) sessions' | |
| :hedis-0.8.3/benchmark/Benchmark.hs | |
| 68;13 9: True <- return $ vs == expected | |
| 74;13 9: True <- return $ pongs == expected | |
| :helisp-0.1/src/Helisp.hs | |
| 9;17 9: asts <- return (parseAst c); | |
| 10;14 9: r <- return (map (eval symbolTable) asts); | |
| 15;17 9: asts <- return (parseAst c); | |
| :helium-1.8.1/src/Helium/CodeGeneration/CodeGeneration.hs | |
| 211;50 9: (T_Alternative_vOut1 _lhsOcore _lhsOself) <- return (inv_Alternative_s2 sem arg) | |
| 369;51 9: (T_Alternatives_vOut4 _lhsOcore _lhsOself) <- return (inv_Alternatives_s5 sem arg) | |
| 464;42 9: (T_AnnotatedType_vOut7 _lhsOself) <- return (inv_AnnotatedType_s8 sem arg) | |
| 518;56 9: (T_AnnotatedTypes_vOut10 _lhsOlength _lhsOself) <- return (inv_AnnotatedTypes_s11 sem arg) | |
| 601;45 9: (T_Body_vOut13 _lhsOdecls _lhsOself) <- return (inv_Body_s14 sem arg) | |
| 705;51 9: (T_Constructor_vOut16 _lhsOcons _lhsOself) <- return (inv_Constructor_s17 sem arg) | |
| 852;52 9: (T_Constructors_vOut19 _lhsOcons _lhsOself) <- return (inv_Constructors_s20 sem arg) | |
| 967;41 9: (T_ContextItem_vOut22 _lhsOself) <- return (inv_ContextItem_s23 sem arg) | |
| 1023;42 9: (T_ContextItems_vOut25 _lhsOself) <- return (inv_ContextItems_s26 sem arg) | |
| 1096;67 9: (T_Declaration_vOut28 _lhsOdecls _lhsOpatBindNr _lhsOself) <- return (inv_Declaration_s29 sem arg) | |
| 1751;68 9: (T_Declarations_vOut31 _lhsOdecls _lhsOpatBindNr _lhsOself) <- return (inv_Declarations_s32 sem arg) | |
| 1876;79 9: (T_Export_vOut34 _lhsOcons _lhsOmods _lhsOself _lhsOtypes _lhsOvalues) <- return (inv_Export_s35 sem arg) | |
| 2084;80 9: (T_Exports_vOut37 _lhsOcons _lhsOmods _lhsOself _lhsOtypes _lhsOvalues) <- return (inv_Exports_s38 sem arg) | |
| 2197;50 9: (T_Expression_vOut40 _lhsOcore _lhsOself) <- return (inv_Expression_s41 sem arg) | |
| 3096;51 9: (T_Expressions_vOut43 _lhsOcore _lhsOself) <- return (inv_Expressions_s44 sem arg) | |
| 3187;46 9: (T_FieldDeclaration_vOut46 _lhsOself) <- return (inv_FieldDeclaration_s47 sem arg) | |
| 3243;47 9: (T_FieldDeclarations_vOut49 _lhsOself) <- return (inv_FieldDeclarations_s50 sem arg) | |
| 3316;36 9: (T_Fixity_vOut52 _lhsOself) <- return (inv_Fixity_s53 sem arg) | |
| 3412;76 9: (T_FunctionBinding_vOut55 _lhsOarity _lhsOcore _lhsOname _lhsOself) <- return (inv_FunctionBinding_s56 sem arg) | |
| 3582;77 9: (T_FunctionBindings_vOut58 _lhsOarity _lhsOcore _lhsOname _lhsOself) <- return (inv_FunctionBindings_s59 sem arg) | |
| 3705;57 9: (T_GuardedExpression_vOut61 _lhsOcore _lhsOself) <- return (inv_GuardedExpression_s62 sem arg) | |
| 3774;58 9: (T_GuardedExpressions_vOut64 _lhsOcore _lhsOself) <- return (inv_GuardedExpressions_s65 sem arg) | |
| 3865;36 9: (T_Import_vOut67 _lhsOself) <- return (inv_Import_s68 sem arg) | |
| 3969;47 9: (T_ImportDeclaration_vOut70 _lhsOself) <- return (inv_ImportDeclaration_s71 sem arg) | |
| 4049;48 9: (T_ImportDeclarations_vOut73 _lhsOself) <- return (inv_ImportDeclarations_s74 sem arg) | |
| 4122;49 9: (T_ImportSpecification_vOut76 _lhsOself) <- return (inv_ImportSpecification_s77 sem arg) | |
| 4176;37 9: (T_Imports_vOut79 _lhsOself) <- return (inv_Imports_s80 sem arg) | |
| 4249;77 9: (T_LeftHandSide_vOut82 _lhsOarity _lhsOname _lhsOpatterns _lhsOself) <- return (inv_LeftHandSide_s83 sem arg) | |
| 4404;47 9: (T_Literal_vOut85 _lhsOcore _lhsOself) <- return (inv_Literal_s86 sem arg) | |
| 4544;57 9: (T_MaybeDeclarations_vOut88 _lhsOcore _lhsOself) <- return (inv_MaybeDeclarations_s89 sem arg) | |
| 4646;85 9: (T_MaybeExports_vOut91 _lhsOcons _lhsOmods _lhsOself _lhsOtypes _lhsOvalues) <- return (inv_MaybeExports_s92 sem arg) | |
| 4758;55 9: (T_MaybeExpression_vOut94 _lhsOcore _lhsOself) <- return (inv_MaybeExpression_s95 sem arg) | |
| 4844;54 9: (T_MaybeImportSpecification_vOut97 _lhsOself) <- return (inv_MaybeImportSpecification_s98 sem arg) | |
| 4916;39 9: (T_MaybeInt_vOut100 _lhsOself) <- return (inv_MaybeInt_s101 sem arg) | |
| 4986;65 9: (T_MaybeName_vOut103 _lhsOisNothing _lhsOname _lhsOself) <- return (inv_MaybeName_s104 sem arg) | |
| 5078;52 9: (T_MaybeNames_vOut106 _lhsOnames _lhsOself) <- return (inv_MaybeNames_s107 sem arg) | |
| 5160;47 9: (T_Module_vOut109 _lhsOcore _lhsOself) <- return (inv_Module_s110 sem arg) | |
| 5239;35 9: (T_Name_vOut112 _lhsOself) <- return (inv_Name_s113 sem arg) | |
| 5341;47 9: (T_Names_vOut115 _lhsOnames _lhsOself) <- return (inv_Names_s116 sem arg) | |
| 5424;48 9: (T_Pattern_vOut118 _lhsOself _lhsOvars) <- return (inv_Pattern_s119 sem arg) | |
| 5897;61 9: (T_Patterns_vOut121 _lhsOlength _lhsOself _lhsOvars) <- return (inv_Patterns_s122 sem arg) | |
| 5990;39 9: (T_Position_vOut124 _lhsOself) <- return (inv_Position_s125 sem arg) | |
| 6060;50 9: (T_Qualifier_vOut127 _lhsOcore _lhsOself) <- return (inv_Qualifier_s128 sem arg) | |
| 6245;51 9: (T_Qualifiers_vOut130 _lhsOcore _lhsOself) <- return (inv_Qualifiers_s131 sem arg) | |
| 6336;36 9: (T_Range_vOut133 _lhsOself) <- return (inv_Range_s134 sem arg) | |
| 6390;54 9: (T_RecordExpressionBinding_vOut136 _lhsOself) <- return (inv_RecordExpressionBinding_s137 sem arg) | |
| 6450;55 9: (T_RecordExpressionBindings_vOut139 _lhsOself) <- return (inv_RecordExpressionBindings_s140 sem arg) | |
| 6531;51 9: (T_RecordPatternBinding_vOut142 _lhsOself) <- return (inv_RecordPatternBinding_s143 sem arg) | |
| 6587;52 9: (T_RecordPatternBindings_vOut145 _lhsOself) <- return (inv_RecordPatternBindings_s146 sem arg) | |
| 6660;69 9: (T_RightHandSide_vOut148 _lhsOcore _lhsOisGuarded _lhsOself) <- return (inv_RightHandSide_s149 sem arg) | |
| 6778;70 9: (T_SimpleType_vOut151 _lhsOname _lhsOself _lhsOtypevariables) <- return (inv_SimpleType_s152 sem arg) | |
| 6844;50 9: (T_Statement_vOut154 _lhsOcore _lhsOself) <- return (inv_Statement_s155 sem arg) | |
| 7037;51 9: (T_Statements_vOut157 _lhsOcore _lhsOself) <- return (inv_Statements_s158 sem arg) | |
| 7128;38 9: (T_Strings_vOut160 _lhsOself) <- return (inv_Strings_s161 sem arg) | |
| 7199;35 9: (T_Type_vOut163 _lhsOself) <- return (inv_Type_s164 sem arg) | |
| 7405;36 9: (T_Types_vOut166 _lhsOself) <- return (inv_Types_s167 sem arg) | |
| :helium-1.8.1/src/Helium/ModuleSystem/ExtractImportDecls.hs | |
| 24;40 9: (T_Alternative_vOut1 _lhsOself) <- return (inv_Alternative_s2 sem arg) | |
| 148;41 9: (T_Alternatives_vOut4 _lhsOself) <- return (inv_Alternatives_s5 sem arg) | |
| 221;42 9: (T_AnnotatedType_vOut7 _lhsOself) <- return (inv_AnnotatedType_s8 sem arg) | |
| 275;44 9: (T_AnnotatedTypes_vOut10 _lhsOself) <- return (inv_AnnotatedTypes_s11 sem arg) | |
| 348;55 9: (T_Body_vOut13 _lhsOcoreImportDecls _lhsOself) <- return (inv_Body_s14 sem arg) | |
| 436;41 9: (T_Constructor_vOut16 _lhsOself) <- return (inv_Constructor_s17 sem arg) | |
| 546;42 9: (T_Constructors_vOut19 _lhsOself) <- return (inv_Constructors_s20 sem arg) | |
| 619;41 9: (T_ContextItem_vOut22 _lhsOself) <- return (inv_ContextItem_s23 sem arg) | |
| 675;42 9: (T_ContextItems_vOut25 _lhsOself) <- return (inv_ContextItems_s26 sem arg) | |
| 748;41 9: (T_Declaration_vOut28 _lhsOself) <- return (inv_Declaration_s29 sem arg) | |
| 1094;42 9: (T_Declarations_vOut31 _lhsOself) <- return (inv_Declarations_s32 sem arg) | |
| 1167;36 9: (T_Export_vOut34 _lhsOself) <- return (inv_Export_s35 sem arg) | |
| 1295;37 9: (T_Exports_vOut37 _lhsOself) <- return (inv_Exports_s38 sem arg) | |
| 1368;40 9: (T_Expression_vOut40 _lhsOself) <- return (inv_Expression_s41 sem arg) | |
| 1976;41 9: (T_Expressions_vOut43 _lhsOself) <- return (inv_Expressions_s44 sem arg) | |
| 2049;46 9: (T_FieldDeclaration_vOut46 _lhsOself) <- return (inv_FieldDeclaration_s47 sem arg) | |
| 2105;47 9: (T_FieldDeclarations_vOut49 _lhsOself) <- return (inv_FieldDeclarations_s50 sem arg) | |
| 2178;36 9: (T_Fixity_vOut52 _lhsOself) <- return (inv_Fixity_s53 sem arg) | |
| 2274;55 9: (T_FunctionBinding_vOut55 _lhsOname _lhsOself) <- return (inv_FunctionBinding_s56 sem arg) | |
| 2391;56 9: (T_FunctionBindings_vOut58 _lhsOname _lhsOself) <- return (inv_FunctionBindings_s59 sem arg) | |
| 2474;47 9: (T_GuardedExpression_vOut61 _lhsOself) <- return (inv_GuardedExpression_s62 sem arg) | |
| 2530;48 9: (T_GuardedExpressions_vOut64 _lhsOself) <- return (inv_GuardedExpressions_s65 sem arg) | |
| 2603;46 9: (T_Import_vOut67 _lhsOimps _lhsOself) <- return (inv_Import_s68 sem arg) | |
| 2722;68 9: (T_ImportDeclaration_vOut70 _lhsOcoreImportDecls _lhsOself) <- return (inv_ImportDeclaration_s71 sem arg) | |
| 2835;69 9: (T_ImportDeclarations_vOut73 _lhsOcoreImportDecls _lhsOself) <- return (inv_ImportDeclarations_s74 sem arg) | |
| 2918;59 9: (T_ImportSpecification_vOut76 _lhsOimps _lhsOself) <- return (inv_ImportSpecification_s77 sem arg) | |
| 2980;47 9: (T_Imports_vOut79 _lhsOimps _lhsOself) <- return (inv_Imports_s80 sem arg) | |
| 3063;52 9: (T_LeftHandSide_vOut82 _lhsOname _lhsOself) <- return (inv_LeftHandSide_s83 sem arg) | |
| 3188;37 9: (T_Literal_vOut85 _lhsOself) <- return (inv_Literal_s86 sem arg) | |
| 3306;47 9: (T_MaybeDeclarations_vOut88 _lhsOself) <- return (inv_MaybeDeclarations_s89 sem arg) | |
| 3378;42 9: (T_MaybeExports_vOut91 _lhsOself) <- return (inv_MaybeExports_s92 sem arg) | |
| 3450;45 9: (T_MaybeExpression_vOut94 _lhsOself) <- return (inv_MaybeExpression_s95 sem arg) | |
| 3522;64 9: (T_MaybeImportSpecification_vOut97 _lhsOimps _lhsOself) <- return (inv_MaybeImportSpecification_s98 sem arg) | |
| 3604;39 9: (T_MaybeInt_vOut100 _lhsOself) <- return (inv_MaybeInt_s101 sem arg) | |
| 3674;65 9: (T_MaybeName_vOut103 _lhsOisNothing _lhsOname _lhsOself) <- return (inv_MaybeName_s104 sem arg) | |
| 3766;52 9: (T_MaybeNames_vOut106 _lhsOnames _lhsOself) <- return (inv_MaybeNames_s107 sem arg) | |
| 3848;58 9: (T_Module_vOut109 _lhsOcoreImportDecls _lhsOself) <- return (inv_Module_s110 sem arg) | |
| 3911;35 9: (T_Name_vOut112 _lhsOself) <- return (inv_Name_s113 sem arg) | |
| 4013;47 9: (T_Names_vOut115 _lhsOnames _lhsOself) <- return (inv_Names_s116 sem arg) | |
| 4096;38 9: (T_Pattern_vOut118 _lhsOself) <- return (inv_Pattern_s119 sem arg) | |
| 4494;39 9: (T_Patterns_vOut121 _lhsOself) <- return (inv_Patterns_s122 sem arg) | |
| 4567;39 9: (T_Position_vOut124 _lhsOself) <- return (inv_Position_s125 sem arg) | |
| 4637;40 9: (T_Qualifier_vOut127 _lhsOself) <- return (inv_Qualifier_s128 sem arg) | |
| 4763;41 9: (T_Qualifiers_vOut130 _lhsOself) <- return (inv_Qualifiers_s131 sem arg) | |
| 4836;36 9: (T_Range_vOut133 _lhsOself) <- return (inv_Range_s134 sem arg) | |
| 4890;54 9: (T_RecordExpressionBinding_vOut136 _lhsOself) <- return (inv_RecordExpressionBinding_s137 sem arg) | |
| 4946;55 9: (T_RecordExpressionBindings_vOut139 _lhsOself) <- return (inv_RecordExpressionBindings_s140 sem arg) | |
| 5019;51 9: (T_RecordPatternBinding_vOut142 _lhsOself) <- return (inv_RecordPatternBinding_s143 sem arg) | |
| 5075;52 9: (T_RecordPatternBindings_vOut145 _lhsOself) <- return (inv_RecordPatternBindings_s146 sem arg) | |
| 5148;44 9: (T_RightHandSide_vOut148 _lhsOself) <- return (inv_RightHandSide_s149 sem arg) | |
| 5230;41 9: (T_SimpleType_vOut151 _lhsOself) <- return (inv_SimpleType_s152 sem arg) | |
| 5286;40 9: (T_Statement_vOut154 _lhsOself) <- return (inv_Statement_s155 sem arg) | |
| 5412;41 9: (T_Statements_vOut157 _lhsOself) <- return (inv_Statements_s158 sem arg) | |
| 5485;38 9: (T_Strings_vOut160 _lhsOself) <- return (inv_Strings_s161 sem arg) | |
| 5556;35 9: (T_Type_vOut163 _lhsOself) <- return (inv_Type_s164 sem arg) | |
| 5762;36 9: (T_Types_vOut166 _lhsOself) <- return (inv_Types_s167 sem arg) | |
| :helium-1.8.1/src/Helium/Parser/ResolveOperators.hs | |
| 215;59 9: (T_Alternative_vOut1 _lhsOresolveErrors _lhsOself) <- return (inv_Alternative_s2 sem arg) | |
| 383;60 9: (T_Alternatives_vOut4 _lhsOresolveErrors _lhsOself) <- return (inv_Alternatives_s5 sem arg) | |
| 482;42 9: (T_AnnotatedType_vOut7 _lhsOself) <- return (inv_AnnotatedType_s8 sem arg) | |
| 536;44 9: (T_AnnotatedTypes_vOut10 _lhsOself) <- return (inv_AnnotatedTypes_s11 sem arg) | |
| 609;53 9: (T_Body_vOut13 _lhsOresolveErrors _lhsOself) <- return (inv_Body_s14 sem arg) | |
| 705;41 9: (T_Constructor_vOut16 _lhsOself) <- return (inv_Constructor_s17 sem arg) | |
| 815;42 9: (T_Constructors_vOut19 _lhsOself) <- return (inv_Constructors_s20 sem arg) | |
| 888;41 9: (T_ContextItem_vOut22 _lhsOself) <- return (inv_ContextItem_s23 sem arg) | |
| 944;42 9: (T_ContextItems_vOut25 _lhsOself) <- return (inv_ContextItems_s26 sem arg) | |
| 1017;60 9: (T_Declaration_vOut28 _lhsOresolveErrors _lhsOself) <- return (inv_Declaration_s29 sem arg) | |
| 1463;61 9: (T_Declarations_vOut31 _lhsOresolveErrors _lhsOself) <- return (inv_Declarations_s32 sem arg) | |
| 1562;36 9: (T_Export_vOut34 _lhsOself) <- return (inv_Export_s35 sem arg) | |
| 1690;37 9: (T_Exports_vOut37 _lhsOself) <- return (inv_Exports_s38 sem arg) | |
| 1763;59 9: (T_Expression_vOut40 _lhsOresolveErrors _lhsOself) <- return (inv_Expression_s41 sem arg) | |
| 2737;60 9: (T_Expressions_vOut43 _lhsOresolveErrors _lhsOself) <- return (inv_Expressions_s44 sem arg) | |
| 2836;46 9: (T_FieldDeclaration_vOut46 _lhsOself) <- return (inv_FieldDeclaration_s47 sem arg) | |
| 2892;47 9: (T_FieldDeclarations_vOut49 _lhsOself) <- return (inv_FieldDeclarations_s50 sem arg) | |
| 2965;36 9: (T_Fixity_vOut52 _lhsOself) <- return (inv_Fixity_s53 sem arg) | |
| 3061;64 9: (T_FunctionBinding_vOut55 _lhsOresolveErrors _lhsOself) <- return (inv_FunctionBinding_s56 sem arg) | |
| 3202;65 9: (T_FunctionBindings_vOut58 _lhsOresolveErrors _lhsOself) <- return (inv_FunctionBindings_s59 sem arg) | |
| 3301;66 9: (T_GuardedExpression_vOut61 _lhsOresolveErrors _lhsOself) <- return (inv_GuardedExpression_s62 sem arg) | |
| 3378;67 9: (T_GuardedExpressions_vOut64 _lhsOresolveErrors _lhsOself) <- return (inv_GuardedExpressions_s65 sem arg) | |
| 3477;36 9: (T_Import_vOut67 _lhsOself) <- return (inv_Import_s68 sem arg) | |
| 3581;47 9: (T_ImportDeclaration_vOut70 _lhsOself) <- return (inv_ImportDeclaration_s71 sem arg) | |
| 3661;48 9: (T_ImportDeclarations_vOut73 _lhsOself) <- return (inv_ImportDeclarations_s74 sem arg) | |
| 3734;49 9: (T_ImportSpecification_vOut76 _lhsOself) <- return (inv_ImportSpecification_s77 sem arg) | |
| 3788;37 9: (T_Imports_vOut79 _lhsOself) <- return (inv_Imports_s80 sem arg) | |
| 3861;61 9: (T_LeftHandSide_vOut82 _lhsOresolveErrors _lhsOself) <- return (inv_LeftHandSide_s83 sem arg) | |
| 4026;37 9: (T_Literal_vOut85 _lhsOself) <- return (inv_Literal_s86 sem arg) | |
| 4144;66 9: (T_MaybeDeclarations_vOut88 _lhsOresolveErrors _lhsOself) <- return (inv_MaybeDeclarations_s89 sem arg) | |
| 4234;42 9: (T_MaybeExports_vOut91 _lhsOself) <- return (inv_MaybeExports_s92 sem arg) | |
| 4306;64 9: (T_MaybeExpression_vOut94 _lhsOresolveErrors _lhsOself) <- return (inv_MaybeExpression_s95 sem arg) | |
| 4396;54 9: (T_MaybeImportSpecification_vOut97 _lhsOself) <- return (inv_MaybeImportSpecification_s98 sem arg) | |
| 4468;39 9: (T_MaybeInt_vOut100 _lhsOself) <- return (inv_MaybeInt_s101 sem arg) | |
| 4538;40 9: (T_MaybeName_vOut103 _lhsOself) <- return (inv_MaybeName_s104 sem arg) | |
| 4610;41 9: (T_MaybeNames_vOut106 _lhsOself) <- return (inv_MaybeNames_s107 sem arg) | |
| 4682;56 9: (T_Module_vOut109 _lhsOresolveErrors _lhsOself) <- return (inv_Module_s110 sem arg) | |
| 4753;35 9: (T_Name_vOut112 _lhsOself) <- return (inv_Name_s113 sem arg) | |
| 4855;36 9: (T_Names_vOut115 _lhsOself) <- return (inv_Names_s116 sem arg) | |
| 4928;57 9: (T_Pattern_vOut118 _lhsOresolveErrors _lhsOself) <- return (inv_Pattern_s119 sem arg) | |
| 5477;58 9: (T_Patterns_vOut121 _lhsOresolveErrors _lhsOself) <- return (inv_Patterns_s122 sem arg) | |
| 5576;39 9: (T_Position_vOut124 _lhsOself) <- return (inv_Position_s125 sem arg) | |
| 5646;59 9: (T_Qualifier_vOut127 _lhsOresolveErrors _lhsOself) <- return (inv_Qualifier_s128 sem arg) | |
| 5824;60 9: (T_Qualifiers_vOut130 _lhsOresolveErrors _lhsOself) <- return (inv_Qualifiers_s131 sem arg) | |
| 5923;36 9: (T_Range_vOut133 _lhsOself) <- return (inv_Range_s134 sem arg) | |
| 5977;73 9: (T_RecordExpressionBinding_vOut136 _lhsOresolveErrors _lhsOself) <- return (inv_RecordExpressionBinding_s137 sem arg) | |
| 6046;74 9: (T_RecordExpressionBindings_vOut139 _lhsOresolveErrors _lhsOself) <- return (inv_RecordExpressionBindings_s140 sem arg) | |
| 6145;70 9: (T_RecordPatternBinding_vOut142 _lhsOresolveErrors _lhsOself) <- return (inv_RecordPatternBinding_s143 sem arg) | |
| 6214;71 9: (T_RecordPatternBindings_vOut145 _lhsOresolveErrors _lhsOself) <- return (inv_RecordPatternBindings_s146 sem arg) | |
| 6313;63 9: (T_RightHandSide_vOut148 _lhsOresolveErrors _lhsOself) <- return (inv_RightHandSide_s149 sem arg) | |
| 6437;41 9: (T_SimpleType_vOut151 _lhsOself) <- return (inv_SimpleType_s152 sem arg) | |
| 6493;59 9: (T_Statement_vOut154 _lhsOresolveErrors _lhsOself) <- return (inv_Statement_s155 sem arg) | |
| 6671;60 9: (T_Statements_vOut157 _lhsOresolveErrors _lhsOself) <- return (inv_Statements_s158 sem arg) | |
| 6770;38 9: (T_Strings_vOut160 _lhsOself) <- return (inv_Strings_s161 sem arg) | |
| 6841;35 9: (T_Type_vOut163 _lhsOself) <- return (inv_Type_s164 sem arg) | |
| 7047;36 9: (T_Types_vOut166 _lhsOself) <- return (inv_Types_s167 sem arg) | |
| :helium-1.8.1/src/Helium/StaticAnalysis/Directives/TS_Analyse.hs | |
| 58;40 9: (T_Alternative_vOut1 _lhsOself) <- return (inv_Alternative_s2 sem arg) | |
| 182;41 9: (T_Alternatives_vOut4 _lhsOself) <- return (inv_Alternatives_s5 sem arg) | |
| 255;42 9: (T_AnnotatedType_vOut7 _lhsOself) <- return (inv_AnnotatedType_s8 sem arg) | |
| 309;44 9: (T_AnnotatedTypes_vOut10 _lhsOself) <- return (inv_AnnotatedTypes_s11 sem arg) | |
| 382;34 9: (T_Body_vOut13 _lhsOself) <- return (inv_Body_s14 sem arg) | |
| 460;41 9: (T_Constructor_vOut16 _lhsOself) <- return (inv_Constructor_s17 sem arg) | |
| 570;42 9: (T_Constructors_vOut19 _lhsOself) <- return (inv_Constructors_s20 sem arg) | |
| 643;41 9: (T_ContextItem_vOut22 _lhsOself) <- return (inv_ContextItem_s23 sem arg) | |
| 699;42 9: (T_ContextItems_vOut25 _lhsOself) <- return (inv_ContextItems_s26 sem arg) | |
| 772;41 9: (T_Declaration_vOut28 _lhsOself) <- return (inv_Declaration_s29 sem arg) | |
| 1118;42 9: (T_Declarations_vOut31 _lhsOself) <- return (inv_Declarations_s32 sem arg) | |
| 1191;36 9: (T_Export_vOut34 _lhsOself) <- return (inv_Export_s35 sem arg) | |
| 1319;37 9: (T_Exports_vOut37 _lhsOself) <- return (inv_Exports_s38 sem arg) | |
| 1392;58 9: (T_Expression_vOut40 _lhsOallVariables _lhsOself) <- return (inv_Expression_s41 sem arg) | |
| 2115;59 9: (T_Expressions_vOut43 _lhsOallVariables _lhsOself) <- return (inv_Expressions_s44 sem arg) | |
| 2198;46 9: (T_FieldDeclaration_vOut46 _lhsOself) <- return (inv_FieldDeclaration_s47 sem arg) | |
| 2254;47 9: (T_FieldDeclarations_vOut49 _lhsOself) <- return (inv_FieldDeclarations_s50 sem arg) | |
| 2327;36 9: (T_Fixity_vOut52 _lhsOself) <- return (inv_Fixity_s53 sem arg) | |
| 2423;45 9: (T_FunctionBinding_vOut55 _lhsOself) <- return (inv_FunctionBinding_s56 sem arg) | |
| 2525;46 9: (T_FunctionBindings_vOut58 _lhsOself) <- return (inv_FunctionBindings_s59 sem arg) | |
| 2598;47 9: (T_GuardedExpression_vOut61 _lhsOself) <- return (inv_GuardedExpression_s62 sem arg) | |
| 2654;48 9: (T_GuardedExpressions_vOut64 _lhsOself) <- return (inv_GuardedExpressions_s65 sem arg) | |
| 2727;36 9: (T_Import_vOut67 _lhsOself) <- return (inv_Import_s68 sem arg) | |
| 2831;47 9: (T_ImportDeclaration_vOut70 _lhsOself) <- return (inv_ImportDeclaration_s71 sem arg) | |
| 2911;48 9: (T_ImportDeclarations_vOut73 _lhsOself) <- return (inv_ImportDeclarations_s74 sem arg) | |
| 2984;49 9: (T_ImportSpecification_vOut76 _lhsOself) <- return (inv_ImportSpecification_s77 sem arg) | |
| 3038;37 9: (T_Imports_vOut79 _lhsOself) <- return (inv_Imports_s80 sem arg) | |
| 3111;115 9: (T_Judgement_vOut82 _lhsOallVariables _lhsOconclusionType _lhsOself _lhsOtheExpression _lhsOtypevariables) <- return (inv_Judgement_s83 sem arg) | |
| 3185;42 9: (T_LeftHandSide_vOut85 _lhsOself) <- return (inv_LeftHandSide_s86 sem arg) | |
| 3295;37 9: (T_Literal_vOut88 _lhsOself) <- return (inv_Literal_s89 sem arg) | |
| 3413;47 9: (T_MaybeDeclarations_vOut91 _lhsOself) <- return (inv_MaybeDeclarations_s92 sem arg) | |
| 3485;42 9: (T_MaybeExports_vOut94 _lhsOself) <- return (inv_MaybeExports_s95 sem arg) | |
| 3557;63 9: (T_MaybeExpression_vOut97 _lhsOallVariables _lhsOself) <- return (inv_MaybeExpression_s98 sem arg) | |
| 3639;55 9: (T_MaybeImportSpecification_vOut100 _lhsOself) <- return (inv_MaybeImportSpecification_s101 sem arg) | |
| 3711;39 9: (T_MaybeInt_vOut103 _lhsOself) <- return (inv_MaybeInt_s104 sem arg) | |
| 3781;40 9: (T_MaybeName_vOut106 _lhsOself) <- return (inv_MaybeName_s107 sem arg) | |
| 3853;41 9: (T_MaybeNames_vOut109 _lhsOself) <- return (inv_MaybeNames_s110 sem arg) | |
| 3925;37 9: (T_Module_vOut112 _lhsOself) <- return (inv_Module_s113 sem arg) | |
| 3983;35 9: (T_Name_vOut115 _lhsOself) <- return (inv_Name_s116 sem arg) | |
| 4085;36 9: (T_Names_vOut118 _lhsOself) <- return (inv_Names_s119 sem arg) | |
| 4158;38 9: (T_Pattern_vOut121 _lhsOself) <- return (inv_Pattern_s122 sem arg) | |
| 4556;39 9: (T_Patterns_vOut124 _lhsOself) <- return (inv_Patterns_s125 sem arg) | |
| 4629;39 9: (T_Position_vOut127 _lhsOself) <- return (inv_Position_s128 sem arg) | |
| 4699;40 9: (T_Qualifier_vOut130 _lhsOself) <- return (inv_Qualifier_s131 sem arg) | |
| 4825;41 9: (T_Qualifiers_vOut133 _lhsOself) <- return (inv_Qualifiers_s134 sem arg) | |
| 4898;36 9: (T_Range_vOut136 _lhsOself) <- return (inv_Range_s137 sem arg) | |
| 4952;54 9: (T_RecordExpressionBinding_vOut139 _lhsOself) <- return (inv_RecordExpressionBinding_s140 sem arg) | |
| 5008;55 9: (T_RecordExpressionBindings_vOut142 _lhsOself) <- return (inv_RecordExpressionBindings_s143 sem arg) | |
| 5081;51 9: (T_RecordPatternBinding_vOut145 _lhsOself) <- return (inv_RecordPatternBinding_s146 sem arg) | |
| 5137;52 9: (T_RecordPatternBindings_vOut148 _lhsOself) <- return (inv_RecordPatternBindings_s149 sem arg) | |
| 5210;44 9: (T_RightHandSide_vOut151 _lhsOself) <- return (inv_RightHandSide_s152 sem arg) | |
| 5292;87 9: (T_SimpleJudgement_vOut154 _lhsOself _lhsOsimpleJudgements _lhsOtypevariables) <- return (inv_SimpleJudgement_s155 sem arg) | |
| 5360;88 9: (T_SimpleJudgements_vOut157 _lhsOself _lhsOsimpleJudgements _lhsOtypevariables) <- return (inv_SimpleJudgements_s158 sem arg) | |
| 5469;41 9: (T_SimpleType_vOut160 _lhsOself) <- return (inv_SimpleType_s161 sem arg) | |
| 5525;40 9: (T_Statement_vOut163 _lhsOself) <- return (inv_Statement_s164 sem arg) | |
| 5651;41 9: (T_Statements_vOut166 _lhsOself) <- return (inv_Statements_s167 sem arg) | |
| 5724;38 9: (T_Strings_vOut169 _lhsOself) <- return (inv_Strings_s170 sem arg) | |
| 5795;54 9: (T_Type_vOut172 _lhsOself _lhsOtypevariables) <- return (inv_Type_s173 sem arg) | |
| 6036;154 9: (T_TypeRule_vOut175 _lhsOconclusionAllVariables _lhsOconclusionExpression _lhsOconclusionType _lhsOself _lhsOsimpleJudgements _lhsOtypevariables) <- return (inv_TypeRule_s176 sem arg) | |
| 6127;55 9: (T_Types_vOut178 _lhsOself _lhsOtypevariables) <- return (inv_Types_s179 sem arg) | |
| 6210;47 9: (T_TypingStrategies_vOut181 _lhsOself) <- return (inv_TypingStrategies_s182 sem arg) | |
| 6291;71 9: (T_TypingStrategy_vOut184 _lhsOerrors _lhsOself _lhsOwarnings) <- return (inv_TypingStrategy_s185 sem arg) | |
| 6525;137 9: (T_UserStatement_vOut187 _lhsOmetaVariableConstraintNames _lhsOself _lhsOtypevariables _lhsOuserConstraints _lhsOuserPredicates) <- return (inv_UserStatement_s188 sem arg) | |
| 6733;138 9: (T_UserStatements_vOut190 _lhsOmetaVariableConstraintNames _lhsOself _lhsOtypevariables _lhsOuserConstraints _lhsOuserPredicates) <- return (inv_UserStatements_s191 sem arg) | |
| :helium-1.8.1/src/Helium/StaticAnalysis/Inferencers/KindInferencing.hs | |
| 90;76 9: (T_Alternative_vOut1 _lhsObindingGroups _lhsOkappaUnique _lhsOself) <- return (inv_Alternative_s2 sem arg) | |
| 270;77 9: (T_Alternatives_vOut4 _lhsObindingGroups _lhsOkappaUnique _lhsOself) <- return (inv_Alternatives_s5 sem arg) | |
| 379;104 9: (T_AnnotatedType_vOut7 _lhsOassumptions _lhsOconstraints _lhsOkappa _lhsOkappaUnique _lhsOself) <- return (inv_AnnotatedType_s8 sem arg) | |
| 465;107 9: (T_AnnotatedTypes_vOut10 _lhsOassumptions _lhsOconstraints _lhsOkappaUnique _lhsOkappas _lhsOself) <- return (inv_AnnotatedTypes_s11 sem arg) | |
| 594;85 9: (T_Body_vOut13 _lhsOconstraints _lhsOenvironment _lhsOkappaUnique _lhsOself) <- return (inv_Body_s14 sem arg) | |
| 722;92 9: (T_Constructor_vOut16 _lhsOassumptions _lhsOconstraints _lhsOkappaUnique _lhsOself) <- return (inv_Constructor_s17 sem arg) | |
| 905;93 9: (T_Constructors_vOut19 _lhsOassumptions _lhsOconstraints _lhsOkappaUnique _lhsOself) <- return (inv_Constructors_s20 sem arg) | |
| 1024;58 9: (T_ContextItem_vOut22 _lhsOkappaUnique _lhsOself) <- return (inv_ContextItem_s23 sem arg) | |
| 1097;59 9: (T_ContextItems_vOut25 _lhsOkappaUnique _lhsOself) <- return (inv_ContextItems_s26 sem arg) | |
| 1188;77 9: (T_Declaration_vOut28 _lhsObindingGroups _lhsOkappaUnique _lhsOself) <- return (inv_Declaration_s29 sem arg) | |
| 1846;78 9: (T_Declarations_vOut31 _lhsObindingGroups _lhsOkappaUnique _lhsOself) <- return (inv_Declarations_s32 sem arg) | |
| 1955;36 9: (T_Export_vOut34 _lhsOself) <- return (inv_Export_s35 sem arg) | |
| 2083;37 9: (T_Exports_vOut37 _lhsOself) <- return (inv_Exports_s38 sem arg) | |
| 2156;76 9: (T_Expression_vOut40 _lhsObindingGroups _lhsOkappaUnique _lhsOself) <- return (inv_Expression_s41 sem arg) | |
| 3258;77 9: (T_Expressions_vOut43 _lhsObindingGroups _lhsOkappaUnique _lhsOself) <- return (inv_Expressions_s44 sem arg) | |
| 3367;63 9: (T_FieldDeclaration_vOut46 _lhsOkappaUnique _lhsOself) <- return (inv_FieldDeclaration_s47 sem arg) | |
| 3440;64 9: (T_FieldDeclarations_vOut49 _lhsOkappaUnique _lhsOself) <- return (inv_FieldDeclarations_s50 sem arg) | |
| 3531;36 9: (T_Fixity_vOut52 _lhsOself) <- return (inv_Fixity_s53 sem arg) | |
| 3627;81 9: (T_FunctionBinding_vOut55 _lhsObindingGroups _lhsOkappaUnique _lhsOself) <- return (inv_FunctionBinding_s56 sem arg) | |
| 3775;82 9: (T_FunctionBindings_vOut58 _lhsObindingGroups _lhsOkappaUnique _lhsOself) <- return (inv_FunctionBindings_s59 sem arg) | |
| 3884;83 9: (T_GuardedExpression_vOut61 _lhsObindingGroups _lhsOkappaUnique _lhsOself) <- return (inv_GuardedExpression_s62 sem arg) | |
| 3966;84 9: (T_GuardedExpressions_vOut64 _lhsObindingGroups _lhsOkappaUnique _lhsOself) <- return (inv_GuardedExpressions_s65 sem arg) | |
| 4075;36 9: (T_Import_vOut67 _lhsOself) <- return (inv_Import_s68 sem arg) | |
| 4179;47 9: (T_ImportDeclaration_vOut70 _lhsOself) <- return (inv_ImportDeclaration_s71 sem arg) | |
| 4259;48 9: (T_ImportDeclarations_vOut73 _lhsOself) <- return (inv_ImportDeclarations_s74 sem arg) | |
| 4332;49 9: (T_ImportSpecification_vOut76 _lhsOself) <- return (inv_ImportSpecification_s77 sem arg) | |
| 4386;37 9: (T_Imports_vOut79 _lhsOself) <- return (inv_Imports_s80 sem arg) | |
| 4459;42 9: (T_LeftHandSide_vOut82 _lhsOself) <- return (inv_LeftHandSide_s83 sem arg) | |
| 4569;37 9: (T_Literal_vOut85 _lhsOself) <- return (inv_Literal_s86 sem arg) | |
| 4687;83 9: (T_MaybeDeclarations_vOut88 _lhsObindingGroups _lhsOkappaUnique _lhsOself) <- return (inv_MaybeDeclarations_s89 sem arg) | |
| 4787;42 9: (T_MaybeExports_vOut91 _lhsOself) <- return (inv_MaybeExports_s92 sem arg) | |
| 4859;81 9: (T_MaybeExpression_vOut94 _lhsObindingGroups _lhsOkappaUnique _lhsOself) <- return (inv_MaybeExpression_s95 sem arg) | |
| 4959;54 9: (T_MaybeImportSpecification_vOut97 _lhsOself) <- return (inv_MaybeImportSpecification_s98 sem arg) | |
| 5031;39 9: (T_MaybeInt_vOut100 _lhsOself) <- return (inv_MaybeInt_s101 sem arg) | |
| 5101;40 9: (T_MaybeName_vOut103 _lhsOself) <- return (inv_MaybeName_s104 sem arg) | |
| 5173;41 9: (T_MaybeNames_vOut106 _lhsOself) <- return (inv_MaybeNames_s107 sem arg) | |
| 5245;87 9: (T_Module_vOut109 _lhsOdebugIO _lhsOkindEnvironment _lhsOkindErrors _lhsOself) <- return (inv_Module_s110 sem arg) | |
| 5335;35 9: (T_Name_vOut112 _lhsOself) <- return (inv_Name_s113 sem arg) | |
| 5437;36 9: (T_Names_vOut115 _lhsOself) <- return (inv_Names_s116 sem arg) | |
| 5510;38 9: (T_Pattern_vOut118 _lhsOself) <- return (inv_Pattern_s119 sem arg) | |
| 5908;39 9: (T_Patterns_vOut121 _lhsOself) <- return (inv_Patterns_s122 sem arg) | |
| 5981;39 9: (T_Position_vOut124 _lhsOself) <- return (inv_Position_s125 sem arg) | |
| 6051;76 9: (T_Qualifier_vOut127 _lhsObindingGroups _lhsOkappaUnique _lhsOself) <- return (inv_Qualifier_s128 sem arg) | |
| 6241;77 9: (T_Qualifiers_vOut130 _lhsObindingGroups _lhsOkappaUnique _lhsOself) <- return (inv_Qualifiers_s131 sem arg) | |
| 6350;36 9: (T_Range_vOut133 _lhsOself) <- return (inv_Range_s134 sem arg) | |
| 6404;90 9: (T_RecordExpressionBinding_vOut136 _lhsObindingGroups _lhsOkappaUnique _lhsOself) <- return (inv_RecordExpressionBinding_s137 sem arg) | |
| 6478;91 9: (T_RecordExpressionBindings_vOut139 _lhsObindingGroups _lhsOkappaUnique _lhsOself) <- return (inv_RecordExpressionBindings_s140 sem arg) | |
| 6587;51 9: (T_RecordPatternBinding_vOut142 _lhsOself) <- return (inv_RecordPatternBinding_s143 sem arg) | |
| 6643;52 9: (T_RecordPatternBindings_vOut145 _lhsOself) <- return (inv_RecordPatternBindings_s146 sem arg) | |
| 6716;80 9: (T_RightHandSide_vOut148 _lhsObindingGroups _lhsOkappaUnique _lhsOself) <- return (inv_RightHandSide_s149 sem arg) | |
| 6850;106 9: (T_SimpleType_vOut151 _lhsOconstraints _lhsOdeclared _lhsOenvironment _lhsOkappaUnique _lhsOself) <- return (inv_SimpleType_s152 sem arg) | |
| 6938;76 9: (T_Statement_vOut154 _lhsObindingGroups _lhsOkappaUnique _lhsOself) <- return (inv_Statement_s155 sem arg) | |
| 7128;77 9: (T_Statements_vOut157 _lhsObindingGroups _lhsOkappaUnique _lhsOself) <- return (inv_Statements_s158 sem arg) | |
| 7237;38 9: (T_Strings_vOut160 _lhsOself) <- return (inv_Strings_s161 sem arg) | |
| 7308;97 9: (T_Type_vOut163 _lhsOassumptions _lhsOconstraints _lhsOkappa _lhsOkappaUnique _lhsOself) <- return (inv_Type_s164 sem arg) | |
| 7734;99 9: (T_Types_vOut166 _lhsOassumptions _lhsOconstraints _lhsOkappaUnique _lhsOkappas _lhsOself) <- return (inv_Types_s167 sem arg) | |
| :helium-1.8.1/src/Helium/StaticAnalysis/Inferencers/TypeInferencing.hs | |
| 610;307 9: (T_Alternative_vOut1 _lhsOassumptions _lhsObetaUnique _lhsOcollectErrors _lhsOcollectInstances _lhsOcollectWarnings _lhsOconstraints _lhsOcounter _lhsOdictionaryEnvironment _lhsOelements _lhsOinfoTrees _lhsOmatchIO _lhsOpatternMatchWarnings _lhsOself _lhsOunboundNames _lhsOuniqueChunk _lhsOunrwar) <- return (inv_Alternative_s2 sem arg) | |
| 1269;314 9: (T_Alternatives_vOut4 _lhsOassumptions _lhsObetaUnique _lhsOcollectErrors _lhsOcollectInstances _lhsOcollectWarnings _lhsOconstraintslist _lhsOcounter _lhsOdictionaryEnvironment _lhsOelementss _lhsOinfoTrees _lhsOmatchIO _lhsOpatternMatchWarnings _lhsOself _lhsOunboundNames _lhsOuniqueChunk _lhsOunrwars) <- return (inv_Alternatives_s5 sem arg) | |
| 1668;73 9: (T_AnnotatedType_vOut7 _lhsOcounter _lhsOself _lhsOunboundNames) <- return (inv_AnnotatedType_s8 sem arg) | |
| 1732;75 9: (T_AnnotatedTypes_vOut10 _lhsOcounter _lhsOself _lhsOunboundNames) <- return (inv_AnnotatedTypes_s11 sem arg) | |
| 1841;311 9: (T_Body_vOut13 _lhsOassumptions _lhsObetaUnique _lhsOcollectErrors _lhsOcollectInstances _lhsOcollectWarnings _lhsOconstraints _lhsOcounter _lhsOdeclVarNames _lhsOdictionaryEnvironment _lhsOinfoTree _lhsOmatchIO _lhsOpatternMatchWarnings _lhsOself _lhsOtoplevelTypes _lhsOunboundNames _lhsOuniqueChunk) <- return (inv_Body_s14 sem arg) | |
| 2196;72 9: (T_Constructor_vOut16 _lhsOcounter _lhsOself _lhsOunboundNames) <- return (inv_Constructor_s17 sem arg) | |
| 2368;73 9: (T_Constructors_vOut19 _lhsOcounter _lhsOself _lhsOunboundNames) <- return (inv_Constructors_s20 sem arg) | |
| 2477;41 9: (T_ContextItem_vOut22 _lhsOself) <- return (inv_ContextItem_s23 sem arg) | |
| 2537;42 9: (T_ContextItems_vOut25 _lhsOself) <- return (inv_ContextItems_s26 sem arg) | |
| 2610;346 9: (T_Declaration_vOut28 _lhsObetaUnique _lhsObindingGroups _lhsOcollectErrors _lhsOcollectInstances _lhsOcollectWarnings _lhsOcounter _lhsOdeclVarNames _lhsOdictionaryEnvironment _lhsOinfoTrees _lhsOmatchIO _lhsOpatternMatchWarnings _lhsOrestrictedNames _lhsOself _lhsOsimplePatNames _lhsOtypeSignatures _lhsOunboundNames _lhsOuniqueChunk) <- return (inv_Declaration_s29 sem arg) | |
| 4461;347 9: (T_Declarations_vOut31 _lhsObetaUnique _lhsObindingGroups _lhsOcollectErrors _lhsOcollectInstances _lhsOcollectWarnings _lhsOcounter _lhsOdeclVarNames _lhsOdictionaryEnvironment _lhsOinfoTrees _lhsOmatchIO _lhsOpatternMatchWarnings _lhsOrestrictedNames _lhsOself _lhsOsimplePatNames _lhsOtypeSignatures _lhsOunboundNames _lhsOuniqueChunk) <- return (inv_Declarations_s32 sem arg) | |
| 4878;36 9: (T_Export_vOut34 _lhsOself) <- return (inv_Export_s35 sem arg) | |
| 5006;37 9: (T_Exports_vOut37 _lhsOself) <- return (inv_Exports_s38 sem arg) | |
| 5079;326 9: (T_Expression_vOut40 _lhsOassumptions _lhsObeta _lhsObetaUnique _lhsOcollectErrors _lhsOcollectInstances _lhsOcollectWarnings _lhsOconstraints _lhsOcounter _lhsOdictionaryEnvironment _lhsOinfoTree _lhsOmatchIO _lhsOmatches _lhsOpatternMatchWarnings _lhsOself _lhsOunboundNames _lhsOuniqueChunk _lhsOuniqueSecondRound) <- return (inv_Expression_s41 sem arg) | |
| 10874;333 9: (T_Expressions_vOut43 _lhsOassumptions _lhsObetaUnique _lhsObetas _lhsOcollectErrors _lhsOcollectInstances _lhsOcollectWarnings _lhsOconstraintslist _lhsOcounter _lhsOdictionaryEnvironment _lhsOinfoTrees _lhsOmatchIO _lhsOmatches _lhsOpatternMatchWarnings _lhsOself _lhsOunboundNames _lhsOuniqueChunk _lhsOuniqueSecondRound) <- return (inv_Expressions_s44 sem arg) | |
| 11275;77 9: (T_FieldDeclaration_vOut46 _lhsOcounter _lhsOself _lhsOunboundNames) <- return (inv_FieldDeclaration_s47 sem arg) | |
| 11353;78 9: (T_FieldDeclarations_vOut49 _lhsOcounter _lhsOself _lhsOunboundNames) <- return (inv_FieldDeclarations_s50 sem arg) | |
| 11462;36 9: (T_Fixity_vOut52 _lhsOself) <- return (inv_Fixity_s53 sem arg) | |
| 11558;357 9: (T_FunctionBinding_vOut55 _lhsOargcount _lhsOassumptions _lhsObetaUnique _lhsOcollectErrors _lhsOcollectInstances _lhsOcollectWarnings _lhsOconstraints _lhsOcounter _lhsOdictionaryEnvironment _lhsOelements _lhsOinfoTree _lhsOmatchIO _lhsOname _lhsOnumberOfPatterns _lhsOpatternMatchWarnings _lhsOself _lhsOunboundNames _lhsOuniqueChunk _lhsOunrwar) <- return (inv_FunctionBinding_s56 sem arg) | |
| 12196;365 9: (T_FunctionBindings_vOut58 _lhsOargcount _lhsOassumptions _lhsObetaUnique _lhsOcollectErrors _lhsOcollectInstances _lhsOcollectWarnings _lhsOconstraintslist _lhsOcounter _lhsOdictionaryEnvironment _lhsOelementss _lhsOinfoTrees _lhsOmatchIO _lhsOname _lhsOnumberOfPatterns _lhsOpatternMatchWarnings _lhsOself _lhsOunboundNames _lhsOuniqueChunk _lhsOunrwars) <- return (inv_FunctionBindings_s59 sem arg) | |
| 12625;351 9: (T_GuardedExpression_vOut61 _lhsOassumptions _lhsObetaUnique _lhsOcollectErrors _lhsOcollectInstances _lhsOcollectWarnings _lhsOconstraints _lhsOcounter _lhsOdictionaryEnvironment _lhsOfallthrough _lhsOinfoTrees _lhsOmatchIO _lhsOpatternMatchWarnings _lhsOrange _lhsOself _lhsOunboundNames _lhsOuniqueChunk _lhsOuniqueSecondRound _lhsOunrwar) <- return (inv_GuardedExpression_s62 sem arg) | |
| 12966;333 9: (T_GuardedExpressions_vOut64 _lhsOassumptions _lhsObetaUnique _lhsOcollectErrors _lhsOcollectInstances _lhsOcollectWarnings _lhsOconstraintslist _lhsOcounter _lhsOdictionaryEnvironment _lhsOfallthrough _lhsOinfoTrees _lhsOmatchIO _lhsOpatternMatchWarnings _lhsOself _lhsOunboundNames _lhsOuniqueChunk _lhsOuniqueSecondRound) <- return (inv_GuardedExpressions_s65 sem arg) | |
| 13378;36 9: (T_Import_vOut67 _lhsOself) <- return (inv_Import_s68 sem arg) | |
| 13482;47 9: (T_ImportDeclaration_vOut70 _lhsOself) <- return (inv_ImportDeclaration_s71 sem arg) | |
| 13562;48 9: (T_ImportDeclarations_vOut73 _lhsOself) <- return (inv_ImportDeclarations_s74 sem arg) | |
| 13635;49 9: (T_ImportSpecification_vOut76 _lhsOself) <- return (inv_ImportSpecification_s77 sem arg) | |
| 13689;37 9: (T_Imports_vOut79 _lhsOself) <- return (inv_Imports_s80 sem arg) | |
| 13762;252 9: (T_LeftHandSide_vOut82 _lhsOargcount _lhsObetaUnique _lhsObetas _lhsOconstraints _lhsOcounter _lhsOelements _lhsOenvironment _lhsOinfoTrees _lhsOname _lhsOnumberOfPatterns _lhsOpatVarNames _lhsOpatternMatchWarnings _lhsOself _lhsOunboundNames) <- return (inv_LeftHandSide_s83 sem arg) | |
| 14221;68 9: (T_Literal_vOut85 _lhsOelements _lhsOliteralType _lhsOself) <- return (inv_Literal_s86 sem arg) | |
| 14379;322 9: (T_MaybeDeclarations_vOut88 _lhsOassumptions _lhsObetaUnique _lhsOcollectErrors _lhsOcollectInstances _lhsOcollectWarnings _lhsOconstraints _lhsOcounter _lhsOdictionaryEnvironment _lhsOinfoTrees _lhsOlocalTypes _lhsOmatchIO _lhsOnamesInScope _lhsOpatternMatchWarnings _lhsOself _lhsOunboundNames _lhsOuniqueChunk) <- return (inv_MaybeDeclarations_s89 sem arg) | |
| 14712;42 9: (T_MaybeExports_vOut91 _lhsOself) <- return (inv_MaybeExports_s92 sem arg) | |
| 14784;345 9: (T_MaybeExpression_vOut94 _lhsOassumptions _lhsObeta _lhsObetaUnique _lhsOcollectErrors _lhsOcollectInstances _lhsOcollectWarnings _lhsOconstraints _lhsOcounter _lhsOdictionaryEnvironment _lhsOinfoTrees _lhsOmatchIO _lhsOmatches _lhsOpatternMatchWarnings _lhsOsection _lhsOself _lhsOunboundNames _lhsOuniqueChunk _lhsOuniqueSecondRound) <- return (inv_MaybeExpression_s95 sem arg) | |
| 15114;54 9: (T_MaybeImportSpecification_vOut97 _lhsOself) <- return (inv_MaybeImportSpecification_s98 sem arg) | |
| 15186;39 9: (T_MaybeInt_vOut100 _lhsOself) <- return (inv_MaybeInt_s101 sem arg) | |
| 15256;40 9: (T_MaybeName_vOut103 _lhsOself) <- return (inv_MaybeName_s104 sem arg) | |
| 15328;41 9: (T_MaybeNames_vOut106 _lhsOself) <- return (inv_MaybeNames_s107 sem arg) | |
| 15400;177 9: (T_Module_vOut109 _lhsOassumptions _lhsOdictionaryEnvironment _lhsOinfoTree _lhsOlogEntries _lhsOself _lhsOsolveResult _lhsOtoplevelTypes _lhsOtypeErrors _lhsOwarnings) <- return (inv_Module_s110 sem arg) | |
| 15640;35 9: (T_Name_vOut112 _lhsOself) <- return (inv_Name_s113 sem arg) | |
| 15742;36 9: (T_Names_vOut115 _lhsOself) <- return (inv_Names_s116 sem arg) | |
| 15815;200 9: (T_Pattern_vOut118 _lhsObeta _lhsObetaUnique _lhsOconstraints _lhsOcounter _lhsOelements _lhsOenvironment _lhsOinfoTree _lhsOpatVarNames _lhsOpatternMatchWarnings _lhsOself _lhsOunboundNames) <- return (inv_Pattern_s119 sem arg) | |
| 17560;230 9: (T_Patterns_vOut121 _lhsObetaUnique _lhsObetas _lhsOconstraintslist _lhsOcounter _lhsOelementss _lhsOenvironment _lhsOinfoTrees _lhsOnumberOfPatterns _lhsOpatVarNames _lhsOpatternMatchWarnings _lhsOself _lhsOunboundNames) <- return (inv_Patterns_s122 sem arg) | |
| 17799;39 9: (T_Position_vOut124 _lhsOself) <- return (inv_Position_s125 sem arg) | |
| 17869;332 9: (T_Qualifier_vOut127 _lhsOassumptions _lhsObetaUnique _lhsOcollectErrors _lhsOcollectInstances _lhsOcollectWarnings _lhsOconstraints _lhsOcounter _lhsOdictionaryEnvironment _lhsOinfoTree _lhsOmatchIO _lhsOmonos _lhsOnamesInScope _lhsOpatternMatchWarnings _lhsOself _lhsOunboundNames _lhsOuniqueChunk _lhsOuniqueSecondRound) <- return (inv_Qualifier_s128 sem arg) | |
| 18740;334 9: (T_Qualifiers_vOut130 _lhsOassumptions _lhsObetaUnique _lhsOcollectErrors _lhsOcollectInstances _lhsOcollectWarnings _lhsOconstraints _lhsOcounter _lhsOdictionaryEnvironment _lhsOinfoTrees _lhsOmatchIO _lhsOmonos _lhsOnamesInScope _lhsOpatternMatchWarnings _lhsOself _lhsOunboundNames _lhsOuniqueChunk _lhsOuniqueSecondRound) <- return (inv_Qualifiers_s131 sem arg) | |
| 19165;36 9: (T_Range_vOut133 _lhsOself) <- return (inv_Range_s134 sem arg) | |
| 19219;217 9: (T_RecordExpressionBinding_vOut136 _lhsOcollectErrors _lhsOcollectInstances _lhsOcollectWarnings _lhsOcounter _lhsOdictionaryEnvironment _lhsOpatternMatchWarnings _lhsOself _lhsOunboundNames _lhsOuniqueChunk) <- return (inv_RecordExpressionBinding_s137 sem arg) | |
| 19415;218 9: (T_RecordExpressionBindings_vOut139 _lhsOcollectErrors _lhsOcollectInstances _lhsOcollectWarnings _lhsOcounter _lhsOdictionaryEnvironment _lhsOpatternMatchWarnings _lhsOself _lhsOunboundNames _lhsOuniqueChunk) <- return (inv_RecordExpressionBindings_s140 sem arg) | |
| 19688;108 9: (T_RecordPatternBinding_vOut142 _lhsOcounter _lhsOpatternMatchWarnings _lhsOself _lhsOunboundNames) <- return (inv_RecordPatternBinding_s143 sem arg) | |
| 19795;109 9: (T_RecordPatternBindings_vOut145 _lhsOcounter _lhsOpatternMatchWarnings _lhsOself _lhsOunboundNames) <- return (inv_RecordPatternBindings_s146 sem arg) | |
| 19922;301 9: (T_RightHandSide_vOut148 _lhsOassumptions _lhsObetaUnique _lhsOcollectErrors _lhsOcollectInstances _lhsOcollectWarnings _lhsOconstraints _lhsOcounter _lhsOdictionaryEnvironment _lhsOfallthrough _lhsOinfoTree _lhsOmatchIO _lhsOpatternMatchWarnings _lhsOself _lhsOunboundNames _lhsOuniqueChunk) <- return (inv_RightHandSide_s149 sem arg) | |
| 20552;70 9: (T_SimpleType_vOut151 _lhsOname _lhsOself _lhsOtypevariables) <- return (inv_SimpleType_s152 sem arg) | |
| 20618;351 9: (T_Statement_vOut154 _lhsOassumptions _lhsObetaUnique _lhsOcollectErrors _lhsOcollectInstances _lhsOcollectWarnings _lhsOconstraints _lhsOcounter _lhsOdictionaryEnvironment _lhsOgeneratorBeta _lhsOinfoTree _lhsOmatchIO _lhsOmonos _lhsOnamesInScope _lhsOpatternMatchWarnings _lhsOself _lhsOunboundNames _lhsOuniqueChunk _lhsOuniqueSecondRound) <- return (inv_Statement_s155 sem arg) | |
| 21513;342 9: (T_Statements_vOut157 _lhsOassumptions _lhsObetaUnique _lhsOcollectErrors _lhsOcollectInstances _lhsOcollectWarnings _lhsOconstraints _lhsOcounter _lhsOdictionaryEnvironment _lhsOgeneratorBeta _lhsOinfoTrees _lhsOmatchIO _lhsOnamesInScope _lhsOpatternMatchWarnings _lhsOself _lhsOunboundNames _lhsOuniqueChunk _lhsOuniqueSecondRound) <- return (inv_Statements_s158 sem arg) | |
| 21946;38 9: (T_Strings_vOut160 _lhsOself) <- return (inv_Strings_s161 sem arg) | |
| 22017;35 9: (T_Type_vOut163 _lhsOself) <- return (inv_Type_s164 sem arg) | |
| 22223;36 9: (T_Types_vOut166 _lhsOself) <- return (inv_Types_s167 sem arg) | |
| :helium-1.8.1/src/Helium/StaticAnalysis/StaticChecks/StaticChecks.hs | |
| 267;162 9: (T_Alternative_vOut1 _lhsOcollectInstances _lhsOcollectScopeInfos _lhsOcounter _lhsOkindErrors _lhsOmiscerrors _lhsOself _lhsOunboundNames _lhsOwarnings) <- return (inv_Alternative_s2 sem arg) | |
| 679;163 9: (T_Alternatives_vOut4 _lhsOcollectInstances _lhsOcollectScopeInfos _lhsOcounter _lhsOkindErrors _lhsOmiscerrors _lhsOself _lhsOunboundNames _lhsOwarnings) <- return (inv_Alternatives_s5 sem arg) | |
| 926;148 9: (T_AnnotatedType_vOut7 _lhsOcounter _lhsOkindErrors _lhsOmiscerrors _lhsOself _lhsOtype _lhsOtypevariables _lhsOunboundNames _lhsOwarnings) <- return (inv_AnnotatedType_s8 sem arg) | |
| 1039;151 9: (T_AnnotatedTypes_vOut10 _lhsOcounter _lhsOkindErrors _lhsOmiscerrors _lhsOself _lhsOtypes _lhsOtypevariables _lhsOunboundNames _lhsOwarnings) <- return (inv_AnnotatedTypes_s11 sem arg) | |
| 1262;321 9: (T_Body_vOut13 _lhsOcollectInstances _lhsOcollectScopeInfos _lhsOcollectTypeConstructors _lhsOcollectTypeSynonyms _lhsOcollectValueConstructors _lhsOcounter _lhsOdeclVarNames _lhsOimportedModules _lhsOkindErrors _lhsOmiscerrors _lhsOoperatorFixities _lhsOself _lhsOtypeSignatures _lhsOunboundNames _lhsOwarnings) <- return (inv_Body_s14 sem arg) | |
| 1573;187 9: (T_Constructor_vOut16 _lhsOcollectValueConstructors _lhsOcounter _lhsOkindErrors _lhsOmiscerrors _lhsOparameterTypes _lhsOself _lhsOtypevariables _lhsOunboundNames _lhsOwarnings) <- return (inv_Constructor_s17 sem arg) | |
| 1955;188 9: (T_Constructors_vOut19 _lhsOcollectValueConstructors _lhsOcounter _lhsOkindErrors _lhsOmiscerrors _lhsOparameterTypes _lhsOself _lhsOtypevariables _lhsOunboundNames _lhsOwarnings) <- return (inv_Constructors_s20 sem arg) | |
| 2204;107 9: (T_ContextItem_vOut22 _lhsOcontextRanges _lhsOcontextVars _lhsOmiscerrors _lhsOself _lhsOwarnings) <- return (inv_ContextItem_s23 sem arg) | |
| 2306;108 9: (T_ContextItems_vOut25 _lhsOcontextRanges _lhsOcontextVars _lhsOmiscerrors _lhsOself _lhsOwarnings) <- return (inv_ContextItems_s26 sem arg) | |
| 2459;370 9: (T_Declaration_vOut28 _lhsOcollectInstances _lhsOcollectScopeInfos _lhsOcollectTypeConstructors _lhsOcollectTypeSynonyms _lhsOcollectValueConstructors _lhsOcounter _lhsOdeclVarNames _lhsOkindErrors _lhsOmiscerrors _lhsOoperatorFixities _lhsOpreviousWasAlsoFB _lhsOrestrictedNames _lhsOself _lhsOsuspiciousFBs _lhsOtypeSignatures _lhsOunboundNames _lhsOwarnings) <- return (inv_Declaration_s29 sem arg) | |
| 4377;371 9: (T_Declarations_vOut31 _lhsOcollectInstances _lhsOcollectScopeInfos _lhsOcollectTypeConstructors _lhsOcollectTypeSynonyms _lhsOcollectValueConstructors _lhsOcounter _lhsOdeclVarNames _lhsOkindErrors _lhsOmiscerrors _lhsOoperatorFixities _lhsOpreviousWasAlsoFB _lhsOrestrictedNames _lhsOself _lhsOsuspiciousFBs _lhsOtypeSignatures _lhsOunboundNames _lhsOwarnings) <- return (inv_Declarations_s32 sem arg) | |
| 4770;54 9: (T_Export_vOut34 _lhsOexportErrors _lhsOself) <- return (inv_Export_s35 sem arg) | |
| 4920;55 9: (T_Exports_vOut37 _lhsOexportErrors _lhsOself) <- return (inv_Exports_s38 sem arg) | |
| 5035;162 9: (T_Expression_vOut40 _lhsOcollectInstances _lhsOcollectScopeInfos _lhsOcounter _lhsOkindErrors _lhsOmiscerrors _lhsOself _lhsOunboundNames _lhsOwarnings) <- return (inv_Expression_s41 sem arg) | |
| 8118;163 9: (T_Expressions_vOut43 _lhsOcollectInstances _lhsOcollectScopeInfos _lhsOcounter _lhsOkindErrors _lhsOmiscerrors _lhsOself _lhsOunboundNames _lhsOwarnings) <- return (inv_Expressions_s44 sem arg) | |
| 8365;93 9: (T_FieldDeclaration_vOut46 _lhsOcounter _lhsOmiscerrors _lhsOself _lhsOunboundNames) <- return (inv_FieldDeclaration_s47 sem arg) | |
| 8480;94 9: (T_FieldDeclarations_vOut49 _lhsOcounter _lhsOmiscerrors _lhsOself _lhsOunboundNames) <- return (inv_FieldDeclarations_s50 sem arg) | |
| 8615;36 9: (T_Fixity_vOut52 _lhsOself) <- return (inv_Fixity_s53 sem arg) | |
| 8711;188 9: (T_FunctionBinding_vOut55 _lhsOarity _lhsOcollectInstances _lhsOcollectScopeInfos _lhsOcounter _lhsOkindErrors _lhsOmiscerrors _lhsOname _lhsOself _lhsOunboundNames _lhsOwarnings) <- return (inv_FunctionBinding_s56 sem arg) | |
| 9092;191 9: (T_FunctionBindings_vOut58 _lhsOarities _lhsOcollectInstances _lhsOcollectScopeInfos _lhsOcounter _lhsOkindErrors _lhsOmiscerrors _lhsOname _lhsOself _lhsOunboundNames _lhsOwarnings) <- return (inv_FunctionBindings_s59 sem arg) | |
| 9359;169 9: (T_GuardedExpression_vOut61 _lhsOcollectInstances _lhsOcollectScopeInfos _lhsOcounter _lhsOkindErrors _lhsOmiscerrors _lhsOself _lhsOunboundNames _lhsOwarnings) <- return (inv_GuardedExpression_s62 sem arg) | |
| 9554;170 9: (T_GuardedExpressions_vOut64 _lhsOcollectInstances _lhsOcollectScopeInfos _lhsOcounter _lhsOkindErrors _lhsOmiscerrors _lhsOself _lhsOunboundNames _lhsOwarnings) <- return (inv_GuardedExpressions_s65 sem arg) | |
| 9801;36 9: (T_Import_vOut67 _lhsOself) <- return (inv_Import_s68 sem arg) | |
| 9905;68 9: (T_ImportDeclaration_vOut70 _lhsOimportedModules _lhsOself) <- return (inv_ImportDeclaration_s71 sem arg) | |
| 9995;69 9: (T_ImportDeclarations_vOut73 _lhsOimportedModules _lhsOself) <- return (inv_ImportDeclarations_s74 sem arg) | |
| 10086;49 9: (T_ImportSpecification_vOut76 _lhsOself) <- return (inv_ImportSpecification_s77 sem arg) | |
| 10140;37 9: (T_Imports_vOut79 _lhsOself) <- return (inv_Imports_s80 sem arg) | |
| 10213;175 9: (T_LeftHandSide_vOut82 _lhsOcollectScopeInfos _lhsOcounter _lhsOmiscerrors _lhsOname _lhsOnumberOfPatterns _lhsOpatVarNames _lhsOself _lhsOunboundNames _lhsOwarnings) <- return (inv_LeftHandSide_s83 sem arg) | |
| 10639;76 9: (T_Literal_vOut85 _lhsOcollectScopeInfos _lhsOmiscerrors _lhsOself) <- return (inv_Literal_s86 sem arg) | |
| 10805;187 9: (T_MaybeDeclarations_vOut88 _lhsOcollectInstances _lhsOcollectScopeInfos _lhsOcounter _lhsOkindErrors _lhsOmiscerrors _lhsOnamesInScope _lhsOself _lhsOunboundNames _lhsOwarnings) <- return (inv_MaybeDeclarations_s89 sem arg) | |
| 11058;60 9: (T_MaybeExports_vOut91 _lhsOexportErrors _lhsOself) <- return (inv_MaybeExports_s92 sem arg) | |
| 11156;167 9: (T_MaybeExpression_vOut94 _lhsOcollectInstances _lhsOcollectScopeInfos _lhsOcounter _lhsOkindErrors _lhsOmiscerrors _lhsOself _lhsOunboundNames _lhsOwarnings) <- return (inv_MaybeExpression_s95 sem arg) | |
| 11350;54 9: (T_MaybeImportSpecification_vOut97 _lhsOself) <- return (inv_MaybeImportSpecification_s98 sem arg) | |
| 11422;39 9: (T_MaybeInt_vOut100 _lhsOself) <- return (inv_MaybeInt_s101 sem arg) | |
| 11492;40 9: (T_MaybeName_vOut103 _lhsOself) <- return (inv_MaybeName_s104 sem arg) | |
| 11564;41 9: (T_MaybeNames_vOut106 _lhsOself) <- return (inv_MaybeNames_s107 sem arg) | |
| 11636;107 9: (T_Module_vOut109 _lhsOcollectEnvironment _lhsOerrors _lhsOself _lhsOtypeSignatures _lhsOwarnings) <- return (inv_Module_s110 sem arg) | |
| 11982;35 9: (T_Name_vOut112 _lhsOself) <- return (inv_Name_s113 sem arg) | |
| 12084;36 9: (T_Names_vOut115 _lhsOself) <- return (inv_Names_s116 sem arg) | |
| 12157;139 9: (T_Pattern_vOut118 _lhsOcollectScopeInfos _lhsOcounter _lhsOmiscerrors _lhsOpatVarNames _lhsOself _lhsOunboundNames _lhsOwarnings) <- return (inv_Pattern_s119 sem arg) | |
| 13394;162 9: (T_Patterns_vOut121 _lhsOcollectScopeInfos _lhsOcounter _lhsOmiscerrors _lhsOnumberOfPatterns _lhsOpatVarNames _lhsOself _lhsOunboundNames _lhsOwarnings) <- return (inv_Patterns_s122 sem arg) | |
| 13617;39 9: (T_Position_vOut124 _lhsOself) <- return (inv_Position_s125 sem arg) | |
| 13687;180 9: (T_Qualifier_vOut127 _lhsOcollectInstances _lhsOcollectScopeInfos _lhsOcounter _lhsOkindErrors _lhsOmiscerrors _lhsOnamesInScope _lhsOself _lhsOunboundNames _lhsOwarnings) <- return (inv_Qualifier_s128 sem arg) | |
| 14222;181 9: (T_Qualifiers_vOut130 _lhsOcollectInstances _lhsOcollectScopeInfos _lhsOcounter _lhsOkindErrors _lhsOmiscerrors _lhsOnamesInScope _lhsOself _lhsOunboundNames _lhsOwarnings) <- return (inv_Qualifiers_s131 sem arg) | |
| 14487;36 9: (T_Range_vOut133 _lhsOself) <- return (inv_Range_s134 sem arg) | |
| 14541;130 9: (T_RecordExpressionBinding_vOut136 _lhsOcollectInstances _lhsOcollectScopeInfos _lhsOcounter _lhsOself _lhsOunboundNames) <- return (inv_RecordExpressionBinding_s137 sem arg) | |
| 14673;131 9: (T_RecordExpressionBindings_vOut139 _lhsOcollectInstances _lhsOcollectScopeInfos _lhsOcounter _lhsOself _lhsOunboundNames) <- return (inv_RecordExpressionBindings_s140 sem arg) | |
| 14834;105 9: (T_RecordPatternBinding_vOut142 _lhsOcollectScopeInfos _lhsOcounter _lhsOself _lhsOunboundNames) <- return (inv_RecordPatternBinding_s143 sem arg) | |
| 14949;106 9: (T_RecordPatternBindings_vOut145 _lhsOcollectScopeInfos _lhsOcounter _lhsOself _lhsOunboundNames) <- return (inv_RecordPatternBindings_s146 sem arg) | |
| 15076;166 9: (T_RightHandSide_vOut148 _lhsOcollectInstances _lhsOcollectScopeInfos _lhsOcounter _lhsOkindErrors _lhsOmiscerrors _lhsOself _lhsOunboundNames _lhsOwarnings) <- return (inv_RightHandSide_s149 sem arg) | |
| 15444;70 9: (T_SimpleType_vOut151 _lhsOname _lhsOself _lhsOtypevariables) <- return (inv_SimpleType_s152 sem arg) | |
| 15510;205 9: (T_Statement_vOut154 _lhsOcollectInstances _lhsOcollectScopeInfos _lhsOcounter _lhsOkindErrors _lhsOlastStatementIsExpr _lhsOmiscerrors _lhsOnamesInScope _lhsOself _lhsOunboundNames _lhsOwarnings) <- return (inv_Statement_s155 sem arg) | |
| 16065;206 9: (T_Statements_vOut157 _lhsOcollectInstances _lhsOcollectScopeInfos _lhsOcounter _lhsOkindErrors _lhsOlastStatementIsExpr _lhsOmiscerrors _lhsOnamesInScope _lhsOself _lhsOunboundNames _lhsOwarnings) <- return (inv_Statements_s158 sem arg) | |
| 16348;38 9: (T_Strings_vOut160 _lhsOself) <- return (inv_Strings_s161 sem arg) | |
| 16419;102 9: (T_Type_vOut163 _lhsOcontextRange _lhsOmiscerrors _lhsOself _lhsOtypevariables _lhsOwarnings) <- return (inv_Type_s164 sem arg) | |
| 16918;85 9: (T_Types_vOut166 _lhsOmiscerrors _lhsOself _lhsOtypevariables _lhsOwarnings) <- return (inv_Types_s167 sem arg) | |
| :helium-1.8.1/src/Helium/Syntax/UHA_OneLine.hs | |
| 54;57 9: (T_Alternative_vOut1 _lhsOoneLineTree _lhsOself) <- return (inv_Alternative_s2 sem arg) | |
| 210;58 9: (T_Alternatives_vOut4 _lhsOoneLineTree _lhsOself) <- return (inv_Alternatives_s5 sem arg) | |
| 293;42 9: (T_AnnotatedType_vOut7 _lhsOself) <- return (inv_AnnotatedType_s8 sem arg) | |
| 347;44 9: (T_AnnotatedTypes_vOut10 _lhsOself) <- return (inv_AnnotatedTypes_s11 sem arg) | |
| 420;34 9: (T_Body_vOut13 _lhsOself) <- return (inv_Body_s14 sem arg) | |
| 498;41 9: (T_Constructor_vOut16 _lhsOself) <- return (inv_Constructor_s17 sem arg) | |
| 608;42 9: (T_Constructors_vOut19 _lhsOself) <- return (inv_Constructors_s20 sem arg) | |
| 681;41 9: (T_ContextItem_vOut22 _lhsOself) <- return (inv_ContextItem_s23 sem arg) | |
| 737;42 9: (T_ContextItems_vOut25 _lhsOself) <- return (inv_ContextItems_s26 sem arg) | |
| 810;58 9: (T_Declaration_vOut28 _lhsOoneLineTree _lhsOself) <- return (inv_Declaration_s29 sem arg) | |
| 1271;59 9: (T_Declarations_vOut31 _lhsOoneLineTree _lhsOself) <- return (inv_Declarations_s32 sem arg) | |
| 1354;36 9: (T_Export_vOut34 _lhsOself) <- return (inv_Export_s35 sem arg) | |
| 1482;37 9: (T_Exports_vOut37 _lhsOself) <- return (inv_Exports_s38 sem arg) | |
| 1555;57 9: (T_Expression_vOut40 _lhsOoneLineTree _lhsOself) <- return (inv_Expression_s41 sem arg) | |
| 2416;58 9: (T_Expressions_vOut43 _lhsOoneLineTree _lhsOself) <- return (inv_Expressions_s44 sem arg) | |
| 2499;46 9: (T_FieldDeclaration_vOut46 _lhsOself) <- return (inv_FieldDeclaration_s47 sem arg) | |
| 2555;47 9: (T_FieldDeclarations_vOut49 _lhsOself) <- return (inv_FieldDeclarations_s50 sem arg) | |
| 2628;36 9: (T_Fixity_vOut52 _lhsOself) <- return (inv_Fixity_s53 sem arg) | |
| 2724;62 9: (T_FunctionBinding_vOut55 _lhsOoneLineTree _lhsOself) <- return (inv_FunctionBinding_s56 sem arg) | |
| 2849;63 9: (T_FunctionBindings_vOut58 _lhsOoneLineTree _lhsOself) <- return (inv_FunctionBindings_s59 sem arg) | |
| 2932;64 9: (T_GuardedExpression_vOut61 _lhsOoneLineTree _lhsOself) <- return (inv_GuardedExpression_s62 sem arg) | |
| 2997;65 9: (T_GuardedExpressions_vOut64 _lhsOoneLineTree _lhsOself) <- return (inv_GuardedExpressions_s65 sem arg) | |
| 3080;36 9: (T_Import_vOut67 _lhsOself) <- return (inv_Import_s68 sem arg) | |
| 3184;47 9: (T_ImportDeclaration_vOut70 _lhsOself) <- return (inv_ImportDeclaration_s71 sem arg) | |
| 3264;48 9: (T_ImportDeclarations_vOut73 _lhsOself) <- return (inv_ImportDeclarations_s74 sem arg) | |
| 3337;49 9: (T_ImportSpecification_vOut76 _lhsOself) <- return (inv_ImportSpecification_s77 sem arg) | |
| 3391;37 9: (T_Imports_vOut79 _lhsOself) <- return (inv_Imports_s80 sem arg) | |
| 3464;59 9: (T_LeftHandSide_vOut82 _lhsOoneLineTree _lhsOself) <- return (inv_LeftHandSide_s83 sem arg) | |
| 3605;54 9: (T_Literal_vOut85 _lhsOoneLineTree _lhsOself) <- return (inv_Literal_s86 sem arg) | |
| 3759;64 9: (T_MaybeDeclarations_vOut88 _lhsOoneLineTree _lhsOself) <- return (inv_MaybeDeclarations_s89 sem arg) | |
| 3849;42 9: (T_MaybeExports_vOut91 _lhsOself) <- return (inv_MaybeExports_s92 sem arg) | |
| 3921;62 9: (T_MaybeExpression_vOut94 _lhsOoneLineTree _lhsOself) <- return (inv_MaybeExpression_s95 sem arg) | |
| 4011;54 9: (T_MaybeImportSpecification_vOut97 _lhsOself) <- return (inv_MaybeImportSpecification_s98 sem arg) | |
| 4083;39 9: (T_MaybeInt_vOut100 _lhsOself) <- return (inv_MaybeInt_s101 sem arg) | |
| 4153;40 9: (T_MaybeName_vOut103 _lhsOself) <- return (inv_MaybeName_s104 sem arg) | |
| 4225;41 9: (T_MaybeNames_vOut106 _lhsOself) <- return (inv_MaybeNames_s107 sem arg) | |
| 4297;37 9: (T_Module_vOut109 _lhsOself) <- return (inv_Module_s110 sem arg) | |
| 4355;101 9: (T_Name_vOut112 _lhsOisIdentifier _lhsOisOperator _lhsOisSpecial _lhsOoneLineTree _lhsOself) <- return (inv_Name_s113 sem arg) | |
| 4529;102 9: (T_Names_vOut115 _lhsOisIdentifier _lhsOisOperator _lhsOisSpecial _lhsOoneLineTree _lhsOself) <- return (inv_Names_s116 sem arg) | |
| 4642;55 9: (T_Pattern_vOut118 _lhsOoneLineTree _lhsOself) <- return (inv_Pattern_s119 sem arg) | |
| 5195;56 9: (T_Patterns_vOut121 _lhsOoneLineTree _lhsOself) <- return (inv_Patterns_s122 sem arg) | |
| 5278;39 9: (T_Position_vOut124 _lhsOself) <- return (inv_Position_s125 sem arg) | |
| 5348;57 9: (T_Qualifier_vOut127 _lhsOoneLineTree _lhsOself) <- return (inv_Qualifier_s128 sem arg) | |
| 5510;58 9: (T_Qualifiers_vOut130 _lhsOoneLineTree _lhsOself) <- return (inv_Qualifiers_s131 sem arg) | |
| 5593;36 9: (T_Range_vOut133 _lhsOself) <- return (inv_Range_s134 sem arg) | |
| 5647;54 9: (T_RecordExpressionBinding_vOut136 _lhsOself) <- return (inv_RecordExpressionBinding_s137 sem arg) | |
| 5703;55 9: (T_RecordExpressionBindings_vOut139 _lhsOself) <- return (inv_RecordExpressionBindings_s140 sem arg) | |
| 5776;51 9: (T_RecordPatternBinding_vOut142 _lhsOself) <- return (inv_RecordPatternBinding_s143 sem arg) | |
| 5832;52 9: (T_RecordPatternBindings_vOut145 _lhsOself) <- return (inv_RecordPatternBindings_s146 sem arg) | |
| 5905;61 9: (T_RightHandSide_vOut148 _lhsOoneLineTree _lhsOself) <- return (inv_RightHandSide_s149 sem arg) | |
| 6015;41 9: (T_SimpleType_vOut151 _lhsOself) <- return (inv_SimpleType_s152 sem arg) | |
| 6071;57 9: (T_Statement_vOut154 _lhsOoneLineTree _lhsOself) <- return (inv_Statement_s155 sem arg) | |
| 6233;58 9: (T_Statements_vOut157 _lhsOoneLineTree _lhsOself) <- return (inv_Statements_s158 sem arg) | |
| 6316;55 9: (T_Strings_vOut160 _lhsOoneLineTree _lhsOself) <- return (inv_Strings_s161 sem arg) | |
| 6397;35 9: (T_Type_vOut163 _lhsOself) <- return (inv_Type_s164 sem arg) | |
| 6603;36 9: (T_Types_vOut166 _lhsOself) <- return (inv_Types_s167 sem arg) | |
| :helium-1.8.1/src/Helium/Syntax/UHA_Pretty.hs | |
| 66;40 9: (T_Alternative_vOut1 _lhsOtext) <- return (inv_Alternative_s2 sem arg) | |
| 186;41 9: (T_Alternatives_vOut4 _lhsOtext) <- return (inv_Alternatives_s5 sem arg) | |
| 251;42 9: (T_AnnotatedType_vOut7 _lhsOtext) <- return (inv_AnnotatedType_s8 sem arg) | |
| 305;44 9: (T_AnnotatedTypes_vOut10 _lhsOtext) <- return (inv_AnnotatedTypes_s11 sem arg) | |
| 370;34 9: (T_Body_vOut13 _lhsOtext) <- return (inv_Body_s14 sem arg) | |
| 451;41 9: (T_Constructor_vOut16 _lhsOtext) <- return (inv_Constructor_s17 sem arg) | |
| 561;42 9: (T_Constructors_vOut19 _lhsOtext) <- return (inv_Constructors_s20 sem arg) | |
| 626;41 9: (T_ContextItem_vOut22 _lhsOtext) <- return (inv_ContextItem_s23 sem arg) | |
| 682;42 9: (T_ContextItems_vOut25 _lhsOtext) <- return (inv_ContextItems_s26 sem arg) | |
| 747;41 9: (T_Declaration_vOut28 _lhsOtext) <- return (inv_Declaration_s29 sem arg) | |
| 1169;42 9: (T_Declarations_vOut31 _lhsOtext) <- return (inv_Declarations_s32 sem arg) | |
| 1234;36 9: (T_Export_vOut34 _lhsOtext) <- return (inv_Export_s35 sem arg) | |
| 1362;37 9: (T_Exports_vOut37 _lhsOtext) <- return (inv_Exports_s38 sem arg) | |
| 1427;40 9: (T_Expression_vOut40 _lhsOtext) <- return (inv_Expression_s41 sem arg) | |
| 2056;41 9: (T_Expressions_vOut43 _lhsOtext) <- return (inv_Expressions_s44 sem arg) | |
| 2121;46 9: (T_FieldDeclaration_vOut46 _lhsOtext) <- return (inv_FieldDeclaration_s47 sem arg) | |
| 2177;47 9: (T_FieldDeclarations_vOut49 _lhsOtext) <- return (inv_FieldDeclarations_s50 sem arg) | |
| 2242;36 9: (T_Fixity_vOut52 _lhsOtext) <- return (inv_Fixity_s53 sem arg) | |
| 2338;45 9: (T_FunctionBinding_vOut55 _lhsOtext) <- return (inv_FunctionBinding_s56 sem arg) | |
| 2436;46 9: (T_FunctionBindings_vOut58 _lhsOtext) <- return (inv_FunctionBindings_s59 sem arg) | |
| 2501;47 9: (T_GuardedExpression_vOut61 _lhsOtext) <- return (inv_GuardedExpression_s62 sem arg) | |
| 2557;48 9: (T_GuardedExpressions_vOut64 _lhsOtext) <- return (inv_GuardedExpressions_s65 sem arg) | |
| 2622;36 9: (T_Import_vOut67 _lhsOtext) <- return (inv_Import_s68 sem arg) | |
| 2726;47 9: (T_ImportDeclaration_vOut70 _lhsOtext) <- return (inv_ImportDeclaration_s71 sem arg) | |
| 2806;48 9: (T_ImportDeclarations_vOut73 _lhsOtext) <- return (inv_ImportDeclarations_s74 sem arg) | |
| 2871;49 9: (T_ImportSpecification_vOut76 _lhsOtext) <- return (inv_ImportSpecification_s77 sem arg) | |
| 2926;37 9: (T_Imports_vOut79 _lhsOtext) <- return (inv_Imports_s80 sem arg) | |
| 2991;42 9: (T_LeftHandSide_vOut82 _lhsOtext) <- return (inv_LeftHandSide_s83 sem arg) | |
| 3101;37 9: (T_Literal_vOut85 _lhsOtext) <- return (inv_Literal_s86 sem arg) | |
| 3219;47 9: (T_MaybeDeclarations_vOut88 _lhsOtext) <- return (inv_MaybeDeclarations_s89 sem arg) | |
| 3293;42 9: (T_MaybeExports_vOut91 _lhsOtext) <- return (inv_MaybeExports_s92 sem arg) | |
| 3365;45 9: (T_MaybeExpression_vOut94 _lhsOtext) <- return (inv_MaybeExpression_s95 sem arg) | |
| 3437;54 9: (T_MaybeImportSpecification_vOut97 _lhsOtext) <- return (inv_MaybeImportSpecification_s98 sem arg) | |
| 3509;39 9: (T_MaybeInt_vOut100 _lhsOtext) <- return (inv_MaybeInt_s101 sem arg) | |
| 3579;40 9: (T_MaybeName_vOut103 _lhsOtext) <- return (inv_MaybeName_s104 sem arg) | |
| 3651;41 9: (T_MaybeNames_vOut106 _lhsOtext) <- return (inv_MaybeNames_s107 sem arg) | |
| 3723;37 9: (T_Module_vOut109 _lhsOtext) <- return (inv_Module_s110 sem arg) | |
| 3794;84 9: (T_Name_vOut112 _lhsOisIdentifier _lhsOisOperator _lhsOisSpecial _lhsOtext) <- return (inv_Name_s113 sem arg) | |
| 3941;85 9: (T_Names_vOut115 _lhsOisIdentifier _lhsOisOperator _lhsOisSpecial _lhsOtext) <- return (inv_Names_s116 sem arg) | |
| 4036;38 9: (T_Pattern_vOut118 _lhsOtext) <- return (inv_Pattern_s119 sem arg) | |
| 4434;39 9: (T_Patterns_vOut121 _lhsOtext) <- return (inv_Patterns_s122 sem arg) | |
| 4499;39 9: (T_Position_vOut124 _lhsOtext) <- return (inv_Position_s125 sem arg) | |
| 4569;40 9: (T_Qualifier_vOut127 _lhsOtext) <- return (inv_Qualifier_s128 sem arg) | |
| 4695;41 9: (T_Qualifiers_vOut130 _lhsOtext) <- return (inv_Qualifiers_s131 sem arg) | |
| 4760;36 9: (T_Range_vOut133 _lhsOtext) <- return (inv_Range_s134 sem arg) | |
| 4814;54 9: (T_RecordExpressionBinding_vOut136 _lhsOtext) <- return (inv_RecordExpressionBinding_s137 sem arg) | |
| 4870;55 9: (T_RecordExpressionBindings_vOut139 _lhsOtext) <- return (inv_RecordExpressionBindings_s140 sem arg) | |
| 4935;51 9: (T_RecordPatternBinding_vOut142 _lhsOtext) <- return (inv_RecordPatternBinding_s143 sem arg) | |
| 4991;52 9: (T_RecordPatternBindings_vOut145 _lhsOtext) <- return (inv_RecordPatternBindings_s146 sem arg) | |
| 5056;44 9: (T_RightHandSide_vOut148 _lhsOtext) <- return (inv_RightHandSide_s149 sem arg) | |
| 5156;41 9: (T_SimpleType_vOut151 _lhsOtext) <- return (inv_SimpleType_s152 sem arg) | |
| 5212;40 9: (T_Statement_vOut154 _lhsOtext) <- return (inv_Statement_s155 sem arg) | |
| 5338;41 9: (T_Statements_vOut157 _lhsOtext) <- return (inv_Statements_s158 sem arg) | |
| 5403;38 9: (T_Strings_vOut160 _lhsOtext) <- return (inv_Strings_s161 sem arg) | |
| 5466;35 9: (T_Type_vOut163 _lhsOtext) <- return (inv_Type_s164 sem arg) | |
| 5683;36 9: (T_Types_vOut166 _lhsOtext) <- return (inv_Types_s167 sem arg) | |
| :hellage-0.1.1/hellage.hs | |
| 34;20 9: (optz, argz, errs) <- return . getOpt Permute options =<< getArgs | |
| :hermit-1.0.1/src/HERMIT/Dictionary/Debug.hs | |
| 55;30 9: either fail (\ e' -> do _ <- return e >>> observeR before | |
| :hermit-1.0.1/src/HERMIT/Dictionary/Local/Cast.hs | |
| 58;16 9: Pair a b <- return $ coercionKind co | |
| 77;21 9: True <- return (isFunTyCon t) | |
| 83;24 9: Type x' <- return e2 | |
| :hermit-1.0.1/src/HERMIT/Dictionary/Local/Let.hs | |
| 486;9 9: lhs <- return (Let bnds e1) >>> alphaLetR | |
| :hermit-1.0.1/src/HERMIT/Dictionary/Reasoning.hs | |
| 314;9 9: qDoc <- return q >>> extractT (pLCoreTC pp) | |
| :hermit-1.0.1/src/HERMIT/Dictionary/Rules.hs | |
| 218;8 9: rs' <- return e' >>> extractT specRules | |
| 236;12 9: lRules' <- return guts >>> extractT specRules -- spec rules on bindings in this module | |
| :hermit-1.0.1/src/HERMIT/Plugin/Renderer.hs | |
| 123;17 9: doc1 <- return b >>> ppT | |
| 124;17 9: doc2 <- return a >>> ppT | |
| :hermit-1.0.1/src/HERMIT/PrettyPrinter/AST.hs | |
| 125;6 9: d <- return tv >>> ppVar | |
| 128;6 9: d <- return ty >>> ppKindOrType | |
| 135;6 9: d <- return co >>> ppCoercion | |
| 138;6 9: d <- return co >>> ppCoercion | |
| 161;7 9: pd <- return p >>> ppUnivCoProvenance | |
| :hermit-1.0.1/src/HERMIT/PrettyPrinter/Clean.hs | |
| 424;6 9: d <- return tv >>> ppVar | |
| 427;6 9: d <- return ty >>> ppKindOrType | |
| 435;6 9: d <- return co >>> ppCoercion | |
| 438;6 9: d <- return co >>> ppCoercion | |
| 481;7 9: pd <- return p >>> ppUnivCoProvenance | |
| 513;8 9: ty1 <- return co1 >>> ppTypeModeR >>> parenExprExceptApp | |
| 514;8 9: ty2 <- return co2 >>> ppTypeModeR >>> parenExprExceptApp | |
| :hermit-1.0.1/src/HERMIT/Shell/Interpreter.hs | |
| 133;53 9:dynCrossApply fs xs = [ r | f <- fs, x <- xs, Just r <- return (dynApply f x)] | |
| :hermit-syb-0.1.0.0/HERMIT/Optimization/SYB.hs | |
| 402;45 9: let f (x, e) = (do (Let (Rec binds2) body) <- return e | |
| 416;45 9: let f (x, e) = (do (Let (Rec binds2) body) <- return e | |
| 422;17 9: (outer, inner) <- return (unzip binds1') | |
| 499;42 9: (con, args, Let (Rec binds) body) <- return alt | |
| :heukarya-0.2.0.2/src/AI/Heukarya/Center.hs | |
| 110;5 9: jg <- return $ smap (fmap (\x->head $ filter (\s -> show s == x) geneList)) strJg | |
| :hgearman-0.1.0.2/Network/Gearman/Client.hs | |
| 22;4 9: _ <- return $ writePacket sk (mkRequest SET_CLIENT_ID i) >> response sk | |
| :hiccup-0.40/Common.hs | |
| 720;42 9: vm <- return (frVars fr) | |
| :hieraclus-0.1.2.1/src/Numeric/Statistics/Clustering/Clustering.hs | |
| 191;11 9: cinfo' <- return . cinfo =<< get | |
| :himerge-0.20/src/Menus.hs | |
| 91;12 9: scrollw <- return $ castToScrolledWindow page | |
| 237;15 9: flagsfound <- return $ map (findIUSEonUSEFlags key allflags) | |
| :hip-1.0.1.2/src/Graphics/Image/Interface/Repa/Internal.hs | |
| 398;7 9: img' <- return $ exchange RP img | |
| 406;7 9: img' <- return $ exchange RS img | |
| :hist-pl-0.3.2/src/NLP/HistPL/Analyse.hs | |
| 111;10 9: _cont <- return (anaCont x) | |
| :HJScript-0.7.0/src/HJScript/Lang.hs | |
| 221;7 9: body <- return . snd =<< (hjsInside $ fun $ v2e args) | |
| :hlcm-0.2.2/Bench.hs | |
| 57;37 9: (dataFile, _thres, _strat, _n, _d) <- return (args !! 0, args !! 1, args !! 2, args !! 3, args !! 4) | |
| :hlcm-0.2.2/Main.hs | |
| 110;31 9: (dataFile, fileType, _thres) <- return (args !! 0, args !! 1, args !! 2) | |
| :hlint-1.9.33/src/Apply.hs | |
| 70;14 9: i <- return $ rawIdeaN Error "Parse error" (mkSrcSpan sl sl) ctxt Nothing [] | |
| 71;14 9: i <- return $ classify [x | SettingClassify x <- s] i | |
| :hlint-1.9.33/src/CmdLine.hs | |
| 34;12 9: cmdPath <- return $ if null cmdPath then ["."] else cmdPath | |
| 35;17 9: cmdExtension <- return $ if null cmdExtension then ["hs", "lhs"] else cmdExtension | |
| 38;12 9: cmdPath <- return $ if null cmdPath then ["."] else cmdPath | |
| 39;17 9: cmdExtension <- return $ if null cmdExtension then ["hs", "lhs"] else cmdExtension | |
| :hlint-1.9.33/src/Hint/Extensions.hs | |
| 24;18 9:main = do {rec {x <- return 1}; print x} | |
| :hlint-1.9.33/src/Hint/ListRec.hs | |
| 117;22 9: FunBind _ [x1,x2] <- return x | |
| 121;35 9: [(BNil, b1), (BCons x xs, b2)] <- return $ sortBy (comparing fst) [(c1,b1), (c2,b2)] | |
| 123;12 9: (ps,b2) <- return $ eliminateArgs ps1 b2 | |
| 132;33 9: (pre, (view -> Var_ v):post) <- return $ splitAt pos xs | |
| 154;49 9: Match _ name ps (UnGuardedRhs _ bod) Nothing <- return x | |
| 162;8 9: [i] <- return $ findIndices isRight ps | |
| :hlint-1.9.33/src/Hint/Match.hs | |
| 186;49 9: (do guard $ not root; InfixApp _ y11 dot y12 <- return $ fromParen y1; guard $ isDot dot; unifyExp nm root x (App an y11 (App an y12 y2))) | |
| :hlint-1.9.33/src/Hint/Monad.hs | |
| 9;31 9: Use let x = y instead of x <- return y, unless x is contained | |
| 23;11 9:yes = do x <- return y; foo x -- @Suggestion do let x = y; foo x | |
| 24;11 9:yes = do x <- return $ y + z; foo x -- do let x = y + z; foo x | |
| 25;10 9:no = do x <- return x; foo x | |
| 26;10 9,25 9:no = do x <- return y; x <- return y; foo x | |
| :hlint-1.9.33/src/HLint.hs | |
| 123;14 9: settings3 <- return [SettingClassify $ Classify Ignore x "" "" | x <- cmdIgnore] | |
| :hlint-1.9.33/src/HSE/All.hs | |
| 71;12 9: str <- return $ fromMaybe str $ stripPrefix "\65279" str -- remove the BOM if it exists, see #130 | |
| 77;22 9: flags <- return $ parseFlagsNoLocations flags | |
| :hlint-1.9.33/src/Test/All.hs | |
| 28;11 9: useSrc <- return $ hasSrc && null files | |
| :hlint-1.9.33/src/Test/InputOutput.hs | |
| 26;7 9: xs <- return $ filter ((==) ".test" . takeExtension) xs | |
| 73;15 9: (want,got) <- return $ matchStarStar (lines output) got | |
| :HList-0.4.2.0/Data/HList/HList.hs | |
| 193;6 9: l <- return (hProxies :: HList (AddProxy l)) | |
| :HList-0.4.2.0/Data/HList/RecordPuns.hs | |
| 25;17 9:>>> [pun| x y |] <- return (x .=. 3 .*. y .=. "hi" .*. emptyRecord) | |
| :HList-0.4.2.0/examples/Cabal.hs | |
| 39;22 9: "repl" : tgt : args <- return args | |
| :HList-0.4.2.0/examples/Properties/LengthDependent.hs | |
| 402;6 9: x <- return (error "hTranspose involution") `asTypeOf` $(hlN n1) True | |
| :HList-0.4.2.0/examples/Properties/LengthIndependent.hs | |
| 341;6 9: v <- return $ map ($ r) [mkVariant lx 'a', mkVariant ly "ly"] | |
| :hLLVM-0.5.0.1/src/Llvm/Data/Conversion/AstSimplification.hs | |
| 119;34 9: ; ia <- return $ LabelString (implicitLbPrefix ++ show i) | |
| :hlongurl-0.9.3/Network/LongURL.hs | |
| 56;85 9: handleResponse r = do { (CurlResponse { respCurlCode = CurlOK, respBody = b }) <- return r; return b } | |
| 59;32 9:getJSArray v = do { (JSArray a) <- return v; return a } | |
| 62;36 9:getJSString v = do { (JSString jss) <- return v; return $ fromJSString jss } | |
| 87;15 9: (Just jsURL) <- return $ lookup "long_url" rec | |
| :hmatrix-0.17.0.2/src/Internal/Vector.hs | |
| 303;6 9: w <- return $! unsafePerformIO $! createVector (dim v) | |
| 308;41 9: x <- return $! inlinePerformIO $! unsafeWith v $! \p -> peekElemOff p k | |
| 312;41 9: x <- return $! inlinePerformIO $! unsafeWith v $! \p -> peekElemOff p k | |
| 314;41 9: _ <- return $! inlinePerformIO $! unsafeWith w' $! \q -> pokeElemOff q k y | |
| 324;38 9: x <- return $! inlinePerformIO $! unsafeWith v $! \p -> peekElemOff p k | |
| 327;38 9: x <- return $! inlinePerformIO $! unsafeWith v $! \p -> peekElemOff p k | |
| 336;6 9: w <- return $! unsafePerformIO $! createVector (dim v) | |
| 341;41 9: x <- return $! inlinePerformIO $! unsafeWith v $! \p -> peekElemOff p k | |
| 345;41 9: x <- return $! inlinePerformIO $! unsafeWith v $! \p -> peekElemOff p k | |
| 347;41 9: _ <- return $! inlinePerformIO $! unsafeWith w' $! \q -> pokeElemOff q k y | |
| 357;38 9: x <- return $! inlinePerformIO $! unsafeWith v $! \p -> peekElemOff p k | |
| 360;38 9: x <- return $! inlinePerformIO $! unsafeWith v $! \p -> peekElemOff p k | |
| :hmidi-0.2.2.1/System/MacOSX/CoreAudio.hs | |
| 216;47 9: poke (castPtr p) (ab_NumberChannels x) ; p <- return $ plusPtr p 4 | |
| 217;47 9: poke (castPtr p) (ab_DataByteSize x) ; p <- return $ plusPtr p 4 | |
| 221;30 9: n <- peek (castPtr p) ; p <- return $ plusPtr p 4 | |
| 222;30 9: s <- peek (castPtr p) ; p <- return $ plusPtr p 4 | |
| 275;47 9: poke (castPtr p) (ats_SampleTime x) ; p <- return $ plusPtr p 8 | |
| 276;47 9: poke (castPtr p) (ats_HostTime x) ; p <- return $ plusPtr p 8 | |
| 277;47 9: poke (castPtr p) (ats_RateScalar x) ; p <- return $ plusPtr p 8 | |
| 278;47 9: poke (castPtr p) (ats_WordClockTime x) ; p <- return $ plusPtr p 8 | |
| 279;47 9: poke (castPtr p) (ats_SMPTETime x) ; p <- return $ plusPtr p 24 | |
| 280;47 9: poke (castPtr p) (ats_Flags x) ; p <- return $ plusPtr p 4 | |
| 284;30 9: s <- peek (castPtr p) ; p <- return $ plusPtr p 8 | |
| 285;30 9: h <- peek (castPtr p) ; p <- return $ plusPtr p 8 | |
| 286;30 9: r <- peek (castPtr p) ; p <- return $ plusPtr p 8 | |
| 287;30 9: w <- peek (castPtr p) ; p <- return $ plusPtr p 8 | |
| 288;30 9: m <- peek (castPtr p) ; p <- return $ plusPtr p 24 | |
| 289;30 9: f <- peek (castPtr p) ; p <- return $ plusPtr p 4 | |
| 316;43 9: poke (castPtr p) (smpte_Counter x) ; p <- return $ plusPtr p 8 | |
| 317;43 9: poke (castPtr p) (smpte_Type x) ; p <- return $ plusPtr p 4 | |
| 318;43 9: poke (castPtr p) (smpte_Flags x) ; p <- return $ plusPtr p 4 | |
| 319;43 9: poke (castPtr p) (smpte_Hours x) ; p <- return $ plusPtr p 2 | |
| 320;43 9: poke (castPtr p) (smpte_Minutes x) ; p <- return $ plusPtr p 2 | |
| 321;43 9: poke (castPtr p) (smpte_Seconds x) ; p <- return $ plusPtr p 2 | |
| 325;30 9: c <- peek (castPtr p) ; p <- return $ plusPtr p 8 | |
| 326;30 9: t <- peek (castPtr p) ; p <- return $ plusPtr p 4 | |
| 327;30 9: f <- peek (castPtr p) ; p <- return $ plusPtr p 4 | |
| 328;30 9: h <- peek (castPtr p) ; p <- return $ plusPtr p 2 | |
| 329;30 9: m <- peek (castPtr p) ; p <- return $ plusPtr p 2 | |
| 330;30 9: s <- peek (castPtr p) ; p <- return $ plusPtr p 2 | |
| :hmidi-0.2.2.1/System/MacOSX/CoreMIDI.hs | |
| 517;34 9: poke (castPtr p) ep ; r <- return (p `plusPtr` ptrsize) | |
| 518;34 9: poke (castPtr r) q ; r <- return (r `plusPtr` ptrsize) | |
| 519;34 9: poke (castPtr r) n ; r <- return (r `plusPtr` 4 ) | |
| 520;34 9: poke (castPtr r) (0::Int32) ; r <- return (r `plusPtr` 4 ) | |
| 521;34 9: poke (castPtr r) cb ; r <- return (r `plusPtr` ptrsize) | |
| :hmidi-0.2.2.1/System/Win32/MIDI.hs | |
| 186;32 9: mid <- peek (castPtr p) ; q <- return (p `plusPtr` 2) | |
| 187;32 9: pid <- peek (castPtr q) ; q <- return (q `plusPtr` 2) | |
| 188;32 9: ver <- peek (castPtr q) ; q <- return (q `plusPtr` 4) | |
| 189;39 9: nam <- peekTString (castPtr q) ; q <- return (q `plusPtr` (4*maxPNAMELEN)) | |
| 210;32 9: mid <- peek (castPtr p) ; q <- return (p `plusPtr` 2) | |
| 211;32 9: pid <- peek (castPtr q) ; q <- return (q `plusPtr` 2) | |
| 212;32 9: ver <- peek (castPtr q) ; q <- return (q `plusPtr` 4) | |
| 213;39 9: nam <- peekTString (castPtr q) ; q <- return (q `plusPtr` (4*maxPNAMELEN)) | |
| 214;32 9: tec <- peek (castPtr p) ; q <- return (p `plusPtr` 2) | |
| 215;32 9: voi <- peek (castPtr p) ; q <- return (p `plusPtr` 2) | |
| 216;32 9: not <- peek (castPtr p) ; q <- return (p `plusPtr` 2) | |
| 217;32 9: chm <- peek (castPtr p) ; q <- return (p `plusPtr` 2) | |
| :hmp3-1.5.2.1/Main.hs | |
| 103;10 9: args <- return . map P.pack =<< getArgs | |
| :hobbits-1.2.2/Data/Binding/Hobbits/Examples/LambdaLifting.hs | |
| 205;29 9: FVUnionRet names sub1 sub2 <- return $ fvUnion fvs1 fvs2 | |
| 208;18 9: PeelRet lc body <- return $ peelLambdas b | |
| 210;17 9: FVSTerm fvs db <- return $ fvSSepLTVars lc llret | |
| :Hoed-0.3.6/Debug/Hoed/Pure/Observe.lhs | |
| 479;12 9:-- c <- return [ClassP cn a'] | |
| 504;10 9: cs <- return [c] | |
| 515;9 9: p <- return $ AppT (ConT cn) a | |
| 516;9 9: q <- return $ AppT (ConT cn) b | |
| 520;9 9: p <- return $ ClassP cn a' | |
| 521;9 9: q <- return $ ClassP cn b' | |
| 523;9 9: c <- return [p,q] | |
| :Hoed-0.3.6/Debug/Hoed/Stk/Observe.lhs | |
| 471;10 9: cs <- return [c] | |
| 482;9 9: p <- return $ AppT (ConT cn) a | |
| 483;9 9: q <- return $ AppT (ConT cn) b | |
| 487;9 9: p <- return $ ClassP cn a' | |
| 488;9 9: q <- return $ ClassP cn b' | |
| 490;9 9: c <- return [p,q] | |
| :Holumbus-Distribution-0.1.1/source/Holumbus/Console/Console.hs | |
| 174;10 9: input <- return (words line) | |
| 175;10 9: cmd <- return (command input) | |
| 176;10 9: args <- return (arguments input) | |
| :Holumbus-Distribution-0.1.1/source/Holumbus/Console/ServerConsole.hs | |
| 160;10 9: input <- return (words line) | |
| 161;10 9: cmd <- return (command input) | |
| 162;10 9: args <- return (arguments input) | |
| :Holumbus-Distribution-0.1.1/source/Holumbus/Distribution/DNode/Network.hs | |
| 226;8 9: d <- return ((fromIntegral (t2 - t1) / 1000000000000) :: Float) | |
| 227;9 9: ds <- return (printf "%.4f" d) | |
| :Holumbus-Distribution-0.1.1/source/Holumbus/Network/Core.hs | |
| 228;8 9: d <- return ((fromIntegral (t2 - t1) / 1000000000000) :: Float) | |
| 229;9 9: ds <- return (printf "%.4f" d) | |
| :Holumbus-Distribution-0.1.1/source/Holumbus/Network/Port.hs | |
| 946;12 9: enc <- return (encode $ p) | |
| 964;12 9: p <- return (decode raw) | |
| :Holumbus-MapReduce-0.1.1/Examples/MapReduce/Crawler/Crawl.hs | |
| 183;12 9: d <- return $ if maxDocs == 0 | |
| 186;12 9: d' <- return $ zip [(cs_nextDocId cs)..] (S.toList d) -- (S.toList $ cs_toBeProcessed cs) | |
| 196;12 9: cs' <- return $ cs { cs_nextDocId = cs_nextDocId cs + length d' | |
| 242;27 9: new <- return $ uri $ fromJust mdoc | |
| 272;22 9: newDoc <- return oldDoc {uri = newUri} | |
| :Holumbus-MapReduce-0.1.1/Examples/MapReduce/Crawler/CrawlerClient.hs | |
| 55;14 9: localDocs <- return $ tmpDocs "" {- (fromMaybe "/tmp" (ic_tempPath idxConfig)) -} docs | |
| :Holumbus-Searchengine-1.2.3/src/Holumbus/Crawler/Core.hs | |
| 234;32 9: m <- return $ unionURIs m1 m2 | |
| 235;32 9: n <- return $ unionURIs' min n1 n2 | |
| 236;32 9: res <- return $ (m, n, r) | |
| :Holumbus-Searchengine-1.2.3/src/Holumbus/Crawler/IndexerCore.hs | |
| 257;41 9: newIxs <- return $ | |
| :Holumbus-Searchengine-1.2.3/src/Holumbus/Crawler/Robots.hs | |
| 107;28 9: s <- return $ evalRobotsTxt agent r | |
| :Holumbus-Storage-0.1.0/source/Holumbus/FileSystem/Storage/FileStorage.hs | |
| 118;14 9: dir <- return (decode raw) | |
| 142;12 9: enc <- return (encode $ fs_Directory stor) | |
| :homeomorphic-0.1/Data/Homeomorphic/MemoCache.hs | |
| 31;12 9: (c2,k2) <- return $ retrieve k c2 | |
| 45;20 9: (c2,y2) <- return $ retrieve y c2 | |
| :hoodle-core-0.15.0/src/Hoodle/View/Coordinate.hs | |
| 70;10 9: (x0,y0) <- return . ((,) <$> fromIntegral.fst <*> fromIntegral.snd ) =<< Gtk.drawWindowGetOrigin win | |
| :hoodle-parser-0.3.0/src/Text/Hoodle/Parse/Zlib.hs | |
| 24;6 9: b <- return . LB.any ( == 0 ) . LB.take 100 =<< LB.hGetContents h | |
| :hoogle-4.2.43/src/Console/Log.hs | |
| 118;20 9: (a,x) <- return $ LBS.break (== '=') x | |
| 121;16 9: x <- return $ LBS.dropWhile isSpace x | |
| 132;15 9: (u,x) <- return $ first LBS.unpack $ LBS.break (== ' ') x | |
| 179;10 9: (a,x) <- return $ LBS.break (== '\"') x | |
| 181;16 9: [(a,x)] <- return $ reads $ LBS.unpack o | |
| 197;10 9: (a,x) <- return $ LBS.break (== '\"') x | |
| 201;10 9: (a,x) <- return $ LBS.break (== ' ') x | |
| :hoogle-4.2.43/src/Hoogle/DataBase/TypeSearch/Graphs.hs | |
| 109;29 9: (Just res,infos) <- return $ IntMap.updateLookupWithKey | |
| 129;22 9: (inf,res) <- return $ addResultAll is query (arg,val) inf | |
| 130;16 9: res <- return $ map (costTypeScore . thd3 &&& id) res | |
| :hoogle-4.2.43/src/Hoogle.hs | |
| 118;14 9: items <- return $ flip map items $ unsafeFmapOnce $ \e -> e{H.entryLocations = map (first $ const "") $ H.entryLocations e, H.entryName="", H.entryText=mempty, H.entryDocs=mempty} | |
| :hoogle-4.2.43/src/Recipe/All.hs | |
| 130;16 9: hoo <- return $ fromMaybe (error $ "Couldn't find hoogle file for " ++ name) hoo | |
| 172;33 9: (deps, contents) <- return $ splitDeps contents | |
| :hoogle-4.2.43/src/Recipe/Cabal.hs | |
| 50;8 9: pkg <- return $ case finalizePackageDescription [] (const True) plat comp [] pkg of | |
| :hoogle-4.2.43/src/Recipe/Hackage.hs | |
| 19;7 9: xs <- return [p </> x | x <- reverse $ sort xs, name == fst (rbreak (== '-') x)] -- make sure highest version comes first | |
| 22;10 9: x <- return $ if b then x </> "html" else x | |
| :hoppy-generator-0.1.0/src/Foreign/Hoppy/Generator/Language/Haskell/Internal.hs | |
| 403;18 9:-- > arg1 <- return arg1' | |
| :hPDB-1.2.0.5/Bio/PDB/IO.hs | |
| 34;41 9: do (structure, errs) <- return $ Bio.PDB.StructureBuilder.parse filename input | |
| :hPDB-examples-1.2.0.2/examples/Rg.hs | |
| 27;8 9: rg <- return $! radiusOfGyration structure | |
| :hpqtypes-1.4.4/src/Database/PostgreSQL/PQTypes/Internal/Notification.hsc | |
| 63;10 9: ntPID <- return . CPid | |
| :hs-captcha-1.0/Graphics/Captcha.hs | |
| 116;8 9: width <- return $ right - left | |
| 117;9 9: height <- return $ top - bottom | |
| 118;10 9: originX <- return $ (captchaSize - width) `div` 2 | |
| 119;10 9: originY <- return $ (captchaSize + height) `div` 2 | |
| :hs-gen-iface-0.5.0/src/hs-gen-iface.hs | |
| 72;6 9: x <- return . fmap HSE.srcInfoSpan . fst | |
| :hs-mesos-0.20.3.0/test/TestFramework.hs | |
| 67;4 9: r <- return "*" -- role to use when registering | |
| 68;9 9: master <- return "127.0.0.1:5050" -- ip:port of master to connect to | |
| :HsASA-0.2/Optimize/Parameter.hs | |
| 172;10 9: p <- return $ (p `advancePtr` 1) | |
| 176;10 9: p <- return $ (p `advancePtr` (1 + numParams (undefined :: a) za)) | |
| 180;10 9: p <- return $ (p `advancePtr` 1) | |
| 188;19 9: un <- return undefined | |
| 189;18 9: p <- return $ (p `advancePtr` numParams un za) | |
| :hsc3-0.15.1/Help/UGen/Buffer/vOsc.help.lhs | |
| 13;24 9:> ;setup i = do {i' <- return (fromIntegral i) | |
| :hsc3-0.15.1/Help/UGen/Buffer/vOsc3.help.lhs | |
| 13;24 9:> ;setup i = do {i' <- return (fromIntegral i) | |
| :hsc3-graphs-0.15/gr/birds-hp.hs | |
| 16;4 9: d <- return . sum =<< sequence (replicate 6 node) | |
| :hsc3-graphs-0.15/gr/birds-m.hs | |
| 23;4 9: d <- return . sum =<< sequence (replicate 6 node) | |
| :hsc3-graphs-0.15/Sound/SC3/Graph/JMCC_birds_hp.hs | |
| 17;4 9: d <- return . sum =<< sequence (replicate 6 node) | |
| :hsc3-graphs-0.15/Sound/SC3/Graph/JMCC_birds_m.hs | |
| 24;4 9: d <- return . sum =<< sequence (replicate 6 node) | |
| :hsdev-0.2.0.0/src/HsDev/Database/Update.hs | |
| 205;3 9: _ <- return $ view inspectionResult im | |
| :hsemail-1.7.7/Text/ParserCombinators/Parsec/Rfc2822.hs | |
| 626;40 9: <|> try (do { r <- return_path; return (ReturnPath r) }) | |
| :HSGEP-0.1.5/GEP/Examples/CADensity/Driver.hs | |
| 54;16 9: bestExpressed <- return $ express_individual (head pop) gnome | |
| 57;13 9: bestString <- return $ infixWalker bestExpressed | |
| :HSGEP-0.1.5/GEP/GenericDriver.hs | |
| 25;31 9: (initialPopulation,rngState) <- return $ runRmonad | |
| 34;17 9: ((best,pop),_) <- return $ runRmonad | |
| :hsgsom-0.2.0/Data/Datamining/Clustering/Gsom/Node.hs | |
| 222;11 9: stop <- return $! error ( | |
| :HsJudy-0.2/Data/Array/Judy/Hash.hs | |
| 88;6 9: m <- return $ Hash fp | |
| :HsJudy-0.2/Data/Array/Judy/IntMap.hs | |
| 92;6 9: m <- return $ IntMap fp | |
| :HsJudy-0.2/Data/Array/Judy/StrMap.hs | |
| 88;6 9: m <- return $ StrMap fp | |
| :hsns-0.5.3/Hsns.hs | |
| 70;5 9: s <- return $ map (\x -> if (x >= 32 && x <= 126) then x else 46) a | |
| 71;5 9: s' <- return $ map (\x -> chr (read $ show x)) s | |
| :HsOpenSSL-0.11.1.1/OpenSSL/X509/Name.hsc | |
| 64;15 9: = do count <- return . fromIntegral =<< failIf (< 0) =<< _entry_count namePtr | |
| :HsSVN-0.4.3.3/Subversion/FileSystem/Revision.hsc | |
| 245;22 9: revNum <- return . fromIntegral =<< peek revNumPtr | |
| :hstidy-0.2/hstidy.hs | |
| 24;13 9: (opts,_,_) <- return . getOpt Permute options =<< getArgs | |
| :hstorchat-0.1.1.0/src/Network/HSTorChat/GUI.hs | |
| 111;21 9: bl <- return . map fromObjRef $ buddylist bs' | |
| :HStringTemplateHelpers-0.0.14/Text/StringTemplate/Helpers.hs | |
| 134;8 9: fs1 <- return . ( filter filt ) =<< getDirectoryContents path | |
| 137;14 9: stmapping <- return . zip (map dropExtension fs) $ templates | |
| :hszephyr-0.1/Network/Zephyr/CBits.hsc | |
| 187;10 9: time <- return $ POSIXTime.posixSecondsToUTCTime (realToFrac (secs :: CTime)) | |
| 191;10 9: fields <- return $ filterFields $ B.split '\0' message | |
| :HTF-0.13.1.0/Test/Framework/Diff.hs | |
| 201;12 9: diff <- return $ multiLineDiffHaskell left right | |
| :html-kure-0.2.1/Text/HTML/KURE.hs | |
| 128;34 9: project u = do HTMLNode t <- return u | |
| 133;37 9: project u = do ElementNode t <- return u | |
| 138;34 9: project u = do TextNode t <- return u | |
| 143;35 9: project u = do AttrsNode t <- return u | |
| 148;34 9: project u = do AttrNode t <- return u | |
| 153;36 9: project u = do SyntaxNode t <- return u | |
| :html-rules-0.1.0.1/src/Text/HTML/Rules.hs | |
| 42;45 9: , one $ do -- <- return a single fragment of HTML. | |
| :http-client-auth-0.1.0.1/src/Network/HTTP/Client/Auth.hs | |
| 173;24 9: do (f, rst) <- return $ span (`notElem` "\"\\") str | |
| 175;35 9: do '"' : tl <- return rst | |
| 179;40 9: do '\\' : c : tl <- return rst | |
| 401;22 9: Just challenge <- return $ getChallenge resp | |
| :husk-scheme-3.19.2/hs-src/Language/Scheme/Compiler/Libraries.hs | |
| 99;15 9: importFunc <- return $ [ | |
| 175;31 9: newEnvFunc <- return $ [ | |
| :husk-scheme-3.19.2/hs-src/Language/Scheme/Compiler.hs | |
| 158;4 9: f <- return $ AstAssignM "x1" $ AstValue val | |
| 159;4 9: c <- return $ createAstCont copts "x1" "" | |
| 169;4 9: f <- return $ fCode | |
| 170;4 9: c <- return $ createAstCont copts "x1" "" | |
| 301;17 9: compFunc <- return $ [ | |
| 326;13 9: compFunc <- return $ [ | |
| 377;6 9: f <- return [AstValue $ " " ++ symPredicate ++ | |
| 395;23 9: compCheckPredicate <- return $ AstFunction symCheckPredicate " env cont result _ " [ | |
| 424;23 9: compMakeDefine <- return $ AstFunction symMakeDefine " env cont result _ " [ | |
| 471;10 9: f <- return $ [ | |
| 473;23 9: compMakeDefine <- return $ AstFunction symMakeDefine " env cont result _ " [ | |
| 496;6 9: f <- return $ [ | |
| 522;6 9: f <- return $ [ | |
| 543;6 9: f <- return $ [ | |
| 564;6 9: f <- return $ [ | |
| 582;6 9: f <- return $ [ | |
| 598;15 9: compDefine <- return $ AstFunction symDefine " env cont chr _ " [ | |
| 603;19 9: compMakeDefine <- return $ AstFunction symMakeDefine " env cont idx (Just [chr]) " [ | |
| 638;15 9: compGetVar <- return $ AstFunction symGetVar " env cont idx _ " [ | |
| 653;12 9: compObj <- return $ AstValue $ "" ++ | |
| 665;14 9: compDoSet <- return $ AstValue $ "" ++ | |
| 701;15 9: compGetVar <- return $ AstFunction symGetVar " env cont idx _ " [ | |
| 714;12 9: compObj <- return $ AstValue $ "" ++ | |
| 729;14 9: compDoSet <- return $ AstValue $ "" ++ | |
| 767;23 9: compiledIdxWrapper <- return $ AstFunction symIdxWrapper " env cont idx _ " [ | |
| 772;19 9: compiledUpdate <- return $ AstFunction symUpdateVec " env cont obj (Just [idx]) " [ | |
| 802;23 9: compiledIdxWrapper <- return $ AstFunction symIdxWrapper " env cont idx _ " [ | |
| 807;19 9: compiledUpdate <- return $ AstFunction symUpdateVec " env cont obj (Just [idx]) " [ | |
| 838;23 9: compiledIdxWrapper <- return $ AstFunction symIdxWrapper " env cont idx _ " [ | |
| 843;19 9: compiledUpdate <- return $ AstFunction symUpdateVec " env cont obj (Just [idx]) " [ | |
| 873;23 9: compiledIdxWrapper <- return $ AstFunction symIdxWrapper " env cont idx _ " [ | |
| 878;19 9: compiledUpdate <- return $ AstFunction symUpdateVec " env cont obj (Just [rkey]) " [ | |
| 909;19 9: compiledUpdate <- return $ AstFunction symDoDelete " env cont rkey _ " [ | |
| 970;4 9: f <- return $ [ | |
| 1083;3 9: f <- return $ [ | |
| 1206;12 9: c <- return $ | |
| 1240;12 9: wrapper <- return $ | |
| 1270;12 9: c <- return $ | |
| :husk-scheme-3.19.2/hs-src/Language/Scheme/Core.hs | |
| 1371;22 9: then do result <- return . last $ results | |
| :hxournal-0.6.6.1/lib/Application/HXournal/Accessor.hs | |
| 152;10 9: cvsInfo <- return . getCanvasInfo cid =<< getSt | |
| 168;10 9: cvsInfo <- return . get currentCanvasInfo =<< getSt | |
| 175;10 9: cvsInfo <- return . getCanvasInfo cid =<< getSt | |
| :hxournal-0.6.6.1/lib/Application/HXournal/Coroutine/Default.hs | |
| 170;12 9: ptype <- return . get (selectType.selectInfo) =<< lift St.get | |
| :hxournal-0.6.6.1/lib/Application/HXournal/Coroutine/File.hs | |
| 68;13 9: xstate'' <- return $ modifyCurrentCanvasInfo (const ncvsinfo) xstate' | |
| 112;22 9: xstateNew <- return $ modifyCurrentCanvasInfo (const ncvsinfo) xstate' | |
| 201;24 9: xstateNew <- return . set currFileName Nothing | |
| :hxournal-0.6.6.1/lib/Application/HXournal/Coroutine/Page.hs | |
| 53;22 9: xstatefinal <- return . modifyCurrentCanvasInfo (const ncvsInfo) $ xstate' | |
| 64;22 9: xstatefinal <- return . modifyCurrentCanvasInfo (const ncvsInfo) $ xstate' | |
| :hxournal-0.6.6.1/lib/Application/HXournal/Coroutine/Select.hs | |
| 281;16 9: xst <- return . set xournalstate (SelectState ntxoj) | |
| :hxournal-0.6.6.1/lib/Application/HXournal/View/Coordinate.hs | |
| 61;10 9: (x0,y0) <- return . ((,) <$> fromIntegral.fst <*> fromIntegral.snd ) =<< drawWindowGetOrigin win | |
| :HXQ-0.20.1/src/withDB/Text/XML/HXQ/DB.hs | |
| 271;13 9: ans <- return True | |
| :i18n-0.3/Text/I18n/Po.hs | |
| 64;14 9: (es,locs) <- return (separateEithers locs) | |
| :idris-0.11.2/Setup.hs | |
| 123;12 9: absPath <- return $ isAbsolute targetDir | |
| 136;57 9: " execDir <- return $ dropFileName expath\n" ++ | |
| :idris-0.11.2/src/Idris/Chaser.hs | |
| 174;28 9: ibcValid <- return True -- hasValidIBCVersion fn | |
| :idris-0.11.2/src/Idris/Core/Elaborate.hs | |
| 346;14 9: n' <- return $! uniqueNameCtxt (context (fst p)) n nouse | |
| :idris-0.11.2/src/Idris/REPL.hs | |
| 1229;36 9: progName <- return $ if isWindows then tmpn ++ ".exe" else tmpn | |
| :idris-0.11.2/src/Pkg/Package.hs | |
| 308;15 9: fn <- return $ if isWindows && not (hasExtension p) | |
| :idris-0.11.2/src/Target_idris.hs | |
| 8;11 9: execDir <- return $ dropFileName expath | |
| :idris-0.11.2/src/Util/System.hs | |
| 92;30 9: tcDir <- return getToolchainDir | |
| 93;33 9: absolute <- return $ isAbsolute tcDir | |
| 94;31 9: target <- return $ | |
| 101;41 9: $ do newPath <- return $ target ++ pathSep ++ path | |
| :idris-0.11.2/test/runtest.hs | |
| 81;28 9: (blacklist, ys) <- return $ break (== "opts") xs | |
| 204;53 9: stackDistDir <- return $ takeWhile (/= '\n') out | |
| :imparse-0.0.0.3/Text/Imparse/Compile/Haskell.hs | |
| 59;12 9: do prefix <- return $ if prefix == "" then "" else prefix ++ "." | |
| 143;12 9: prefix <- return $ if prefix == "" then "" else prefix ++ "." | |
| 184;17 9: ves <- return $ [("v" ++ show k, es!!k) | k <- [0..length es-1]] | |
| 222;12 9: prefix <- return $ if prefix == "" then "" else prefix ++ "." | |
| 228;21 9: reservedOpNames <- return $ nub $ S.allOps p | |
| 229;15 9: opLetters <- return $ nub $ [c | c <- concat reservedOpNames, not $ isAlphaNum c] | |
| 230;19 9: reservedNames <- return $ (nub [r | Explicit r <- terminals p]) \\ reservedOpNames | |
| 297;22 9: do ops <- return $ join "," $ | |
| 346;17 9: do ves <- return $ [("v" ++ show k, es!!k) | k <- [0..length es-1]] | |
| :imparse-0.0.0.3/Text/Imparse.hs | |
| 70;9 9: ; r <- return $ (parseParser s :: Either String (Parser Analysis)) | |
| 80;9 9: do { r <- return $ parseParser str | |
| 128;23 9: do { parser <- return $ analyze parser | |
| 129;30 9: ; (fname, fdir) <- return $ (fileNamePrefix fname, fileNameDir fname) | |
| 150;34 9: do moduleName <- return $ (\(c:cs) -> toUpper c : cs) fname | |
| :imperative-edsl-vhdl-0.3.2/src/Language/Embedded/VHDL/Command.hs | |
| 445;7 9: r <- return $ M.declRecord i rs | |
| :inch-0.2.0/src/Language/Inch/Erase.lhs | |
| 50;18 9:> k :-> _ <- return $ getTyKind f | |
| :informative-0.1.0.27/Web/Informative.hs | |
| 221;10 9: submitR <- return $ toParent $ EditR rid | |
| 244;10 9: submitR <- return $ toParent $ InsertR rid | |
| 245;8 9: msect <- return (Nothing :: Maybe (Either Html [[Html]])) | |
| 246;7 9: kind <- return Article | |
| 247;6 9: fmt <- return LaTeX | |
| 270;10 9: submitR <- return $ toParent $ PrependR rid | |
| 271;8 9: msect <- return (Nothing :: Maybe (Either Html [[Html]])) | |
| 272;7 9: kind <- return Article | |
| 273;6 9: fmt <- return LaTeX | |
| 290;10 9: submitR <- return $ toParent $ CreateR page | |
| 291;8 9: msect <- return (Nothing :: Maybe (Either Html [[Html]])) | |
| 292;7 9: kind <- return Article | |
| 293;6 9: fmt <- return LaTeX | |
| 321;10 9: submitR <- return $ toParent $ EditR rid | |
| 337;11 9: kind <- return k | |
| 338;12 9: msect <- return $ Just $ convSect k (source f lg ln) c | |
| 339;12 9: mprec <- return $ Just c | |
| 369;8 9: msect <- return (Nothing :: Maybe (Either Html [[Html]])) | |
| 372;7 9: kind <- return Article | |
| 373;6 9: fmt <- return LaTeX | |
| 374;10 9: submitR <- return $ toParent $ InsertR rid | |
| 393;11 9: kind <- return k | |
| 394;12 9: msect <- return $ Just $ convSect k (source f lg ln) c | |
| 395;12 9: mprec <- return $ Just c | |
| 425;8 9: msect <- return (Nothing :: Maybe (Either Html [[Html]])) | |
| 428;7 9: kind <- return Article | |
| 429;6 9: fmt <- return LaTeX | |
| 430;10 9: submitR <- return $ toParent $ PrependR rid | |
| 449;11 9: kind <- return k | |
| 450;12 9: msect <- return $ Just $ convSect k (source f lg ln) c | |
| 451;12 9: mprec <- return $ Just c | |
| 473;8 9: msect <- return (Nothing :: Maybe (Either Html [[Html]])) | |
| 476;7 9: kind <- return Article | |
| 477;6 9: fmt <- return LaTeX | |
| 478;10 9: submitR <- return $ toParent $ CreateR page | |
| 488;11 9: kind <- return k | |
| 489;12 9: msect <- return $ Just $ convSect k (source f lg ln) c | |
| 490;12 9: mprec <- return $ Just c | |
| :inline-r-0.8.0.1/tests/Test/GC.hs | |
| 39;16 9: y <- return $ R.release x | |
| :inline-r-0.8.0.1/tests/Test/Vector.hs | |
| 136;17 9: !mutV <- return $ VM.fromSEXP s | |
| 137;17 9: !immV <- return $ V.fromSEXP s | |
| :inline-r-0.8.0.1/tests/tests.hs | |
| 83;11 9: True <- return $ R.typeOf val == R.Env | |
| 88;23 9: True <- return $ (R.unsexp a) == (R.unsexp key) | |
| 89;23 9: True <- return $ (R.unsexp b) == (R.unsexp val) | |
| :intero-0.1.11/src/InteractiveUI.hs | |
| 2505;19 9: linkinfo <- return dflags2 | |
| :ipatch-0.1.1/src/IPatch/Common.hs | |
| 106;38 9: (repo :: Repository p r r' r) <- return $ unsafeUnseal2 (Sealed2 repo) | |
| 129;34 9: (repo :: Repository p r u' t) <- return $ unsafeUnseal2 (Sealed2 repo) | |
| :ipopt-hs-0.5.1.0/Ipopt/NLP.hs | |
| 244;23 9: Just sUniq <- return $ find (`M.notMember` m) $ s : iterate (++"_") (s ++ show n) | |
| :iterIO-0.2.2/Data/IterIO/Extra.hs | |
| 108;10 9: c <- return $ a + b | |
| :ivor-0.1.14.1/Ivor/PatternDefs.lhs | |
| 44;7 9:> wf <- return True | |
| :ivory-0.1.0.3/src/Ivory/Language/Syntax/Concrete/QQ/TypeQQ.hs | |
| 115;4 9: n <- return (mkName v) | |
| :ixmonad-0.57/examples/Counter.hs | |
| 21;11 9:foo = do x <- return 2 | |
| 22;11 9: y <- return 4 | |
| 29;12 9: y <- return 3 | |
| :j2hs-0.99.1/dist/build/j2hs/j2hs-tmp/CodeGen/JavaBindings.hs | |
| 43;18 9: moduleComment <- return ((\_ -> let { __ = | |
| 48;18 9: moduleImports <- return deps | |
| 50;18 9: moduleExports <- return deps | |
| 194;18 9: moduleComment <- return "" | |
| 195;18 9: moduleExports <- return ((\_ -> let { __ = | |
| 324;18 9: moduleComment <- return ((\_ -> let { __ = | |
| :j2hs-0.99.1/dist/build/j2hs/j2hs-tmp/Java2Haskell.hs | |
| 67;22 9: targetDir <- return (opts `get` optTargetDirectory) | |
| :j2hs-0.99.1/src/CodeGen/JavaBindings.hss | |
| 46;18 9: moduleComment <- return """The @#{packageName}@ package.""" | |
| 47;18 9: moduleImports <- return deps | |
| 49;18 9: moduleExports <- return deps | |
| 151;18 9: moduleComment <- return "" | |
| 152;18 9: moduleExports <- return """ | |
| 298;18 9: moduleComment <- return """See "#{moduleName}" for the available methods.""" | |
| :j2hs-0.99.1/src/Java2Haskell.hss | |
| 67;22 9: targetDir <- return (opts `get` optTargetDirectory) | |
| :jarfind-0.1.0.3/JarFind.hs | |
| 153;15 9: cpPosArray <- return $ runSTUArray (toArray' (0,n-1) cpPosList) | |
| :java-bridge-0.20130606.3/dist/build/j2hs/j2hs-tmp/Java2Haskell.hs | |
| 81;14 9: targetDir <- return (opts `get` optTargetDirectory) | |
| :java-bridge-0.20130606.3/j2hs/Java2Haskell.hss | |
| 81;14 9: targetDir <- return (opts `get` optTargetDirectory) | |
| :json-python-0.4.0.1/Python.hs | |
| 172;6 9: y <- return (unpack . encode $ x) | |
| 188;8 9: key <- return $ hash s | |
| :jvm-parser-0.2.1/src/Language/JVM/Parser.hs | |
| 547;20 9: defaultBranch <- return . (address +) . fromIntegral =<< (get :: Get Int32) | |
| 742;9 9: name <- return . poolUtf8 cp =<< getWord16be | |
| 743;12 9: fldType <- return . fst . parseTypeDescriptor . poolUtf8 cp =<< getWord16be | |
| :language-eiffel-0.1.2/Language/Eiffel/Parser/Typ.hs | |
| 53;6 9: p <- return Nothing -- optionMaybe (angles procGen) | |
| 54;6 9: ps <- return [] -- option [] procGens | |
| :language-fortran-0.5.1/dist/build/Language/Fortran/Parser.hs | |
| 5338;16 9: ( do { (fs, n) <- return $ happy_var_7; | |
| 5358;16 9: ( do { (fs, n) <- return $ happy_var_6; | |
| 5378;16 9: ( do { (fs, n) <- return $ happy_var_6; | |
| :lazyio-0.1.0.3/src/System/IO/Lazy.hs | |
| 85;61 9:run $ do x <- interleave getLine; y <- interleave getLine; a <- return (x,y); return (fst a) | |
| :leaky-0.4.0.0/leaky-full-incl-types.hs | |
| 420;9 9: rslt <- return $! duty g pat state' 0 -- force the head? | |
| :leaky-0.4.0.0/leaky-full.hs | |
| 376;9 9: rslt <- return $! duty g pat state' 0 -- force the head? | |
| :leaky-0.4.0.0/leaky.hs | |
| 376;9 9: rslt <- return $! duty g pat state' 0 -- force the head? | |
| :lens-family-th-0.5.0.0/Lens/Family/THCore.hs | |
| 148;11 9: sig <- return [] -- TODO | |
| :lhc-0.10/lib/base/src/Data/HashTable.hs | |
| 357;27 9: (bckt', inserts, result) <- return $ bucketFn bckt | |
| :lhc-0.10/lib/base/src/GHC/IO/Handle/FD.hs | |
| 205;7 9: fd <- return fd0 | |
| :lhc-0.10/src/Grin/HPT/FastSolve.hs | |
| 44;24 9: = do live <- return (reverse $ Map.toList eqs) -- gets (HM.toList . hptLiveSet) | |
| :lhs2tex-1.19/Setup.hs | |
| 78;47 9: b <- return . stripQuotes . stripNewlines $ b | |
| 79;47 9: ex <- return (not . all isSpace $ b) -- or check if directory exists? | |
| 88;44 9: p <- return . stripNewlines $ p | |
| :libcspm-1.0.0/src/CSPM/Desugar.hs | |
| 343;11 9: dp <- return Prefix $$ desugar e1 $$ desugar fs $$ desugar e2 | |
| :libhbb-0.4.1.0/Language/Haskell/HBB/OccurrencesOf.hs | |
| 102;24 9: definitions <- return $ realSrcSpansOfBinding (c2 - c1) bind | |
| :libjenkins-0.8.3/src/Jenkins/Discover.hs | |
| 81;4 9: i <- return (Map.lookup "server-id" m) | |
| 82;4 9: p <- return (Map.lookup "slave-port" m) | |
| :liboleg-2010.1.10.0/Language/TypeCheck.hs | |
| 212;21 9: AsArrow _ arr_cast <- return $ as_arrow t1 | |
| :liquidhaskell-0.6.0.0/tests/neg/Variance1.hs | |
| 10;6 9: _ <- return () | |
| :liquidhaskell-0.6.0.0/tests/pos/Invariants.hs | |
| 15;11 9:foo = do a <- return 0 | |
| :list-t-attoparsec-0.4.0.2/hspec/Main.hs | |
| 19;15 9: head <- return $ fmap fst result | |
| :lit-0.1.10.0/src/Process.hs | |
| 22;12 9: encoded <- return $ encode stream file | |
| :llvm-3.2.0.2/LLVM/Core/Instructions.hs | |
| 154;10 9: tsize <- return 1 | |
| :llvm-general-3.5.1.2/src/LLVM/General/Internal/Instruction.hs | |
| 106;14 9: cases <- return zip `ap` peekArray nCases values `ap` peekArray nCases dests | |
| :llvm-general-3.5.1.2/src/LLVM/General/Internal/Metadata.hs | |
| 41;16 9: csls <- return zip | |
| :llvm-general-3.5.1.2/src/LLVM/General/Internal/Module.hs | |
| 358;4 9: c <- return Context `ap` liftIO (FFI.getModuleContext mod) | |
| :llvm-general-3.5.1.2/test/LLVM/General/Test/Instrumentation.hs | |
| 141;82 9: let names ast = [ n | GlobalDefinition d <- moduleDefinitions ast, Name n <- return (G.name d) ] | |
| :llvm-tf-3.0.3.1/src/LLVM/Core/Instructions.hs | |
| 169;10 9: tsize <- return 1 | |
| :loopy-0.0.1/Avalon.hs | |
| 65;4 9: fw <- return$ fileToFoodweb fp | |
| :loopy-0.0.1/DotFile.hs | |
| 164;6 8: stabs<-return $ res | |
| :loopy-0.0.1/FeedingRates.hs | |
| 27;8 9: src <- return $ dropWhile null $ map (dropWhile isSpace) $ lines src | |
| :loopy-0.0.1/Main.hs | |
| 241;3 9: z <- return $ z{cm=getCommat z} -- FIXME: Reorder to remove this | |
| 344;3 9: ss<- return $breakList (n+1) stabs | |
| 405;3 9: ss<- return $breakList (n+1) sumAlphas | |
| 452;3 9: ss<- return $breakList (n+1) stabs | |
| 461;3 9: ss<- return $breakList (n+1) stabs | |
| 471;3 9: ss<- return $breakList (n+1) sumAlphas | |
| 482;3 9: ss<- return $breakList (n1+1) stabs | |
| :loopy-0.0.1/Stab.hs | |
| 89;7 8: alphas<-return $ res | |
| 103;6 8: stabs<-return $ res | |
| 108;7 8: --res1<-return $readStabs | |
| 109;4 8: old<-return $ [0.0002,0.006,0.0005,0.0003,0.277,0.374,0.259,0.134,0.0092,0.0126,0.0107,0.0354,0.317,0.14,0.223,0.205,0.0001,0.0001,0,0.0001,0.359,0.251,0.309,0.29,0.235,0.178,0.124,0.24,0.204,0.42,0.459,0.285] :: [Double] | |
| 175;4 8: res<-return $ zip props stabs | |
| 185;2 9: n<- return $length x | |
| 186;5 8: prop<-return$ [x!!y!!(cn-1) | y<-[(lm-2)..(n-1)]]--check this is correct regarding the n-1 bit | |
| 187;6 8: prop2<-return $map maybeRead prop | |
| 212;2 9: n<- return $length x | |
| 213;5 8: prop<-return$ [x!!y!!8 | y<-[(lm-2)..(n-1)]]--check this is correct regarding the n-1 bit | |
| 215;6 8: prop2<-return $map read prop | |
| 246;4 9: s2 <- return $ read s :: IO [(String,Double)] | |
| 248;4 9: p2 <- return $ read p :: IO [String] --need to read as double if number | |
| 249;6 9: stabs<- return $ map snd s2 | |
| 250;4 9: res<- return $ zip p2 stabs | |
| :loopy-0.0.1/Types.hs | |
| 49;8 9: output <- return $ splitString (lines (formatString input)) | |
| 78;26 9: output :: [Matrix String]<- return (map toMatrix (splitString (lines (formatString input)))) | |
| 80;7 9: names <- return [ ("input/" ++ dropExtension file ++ show i ++".txt")| i <- [1..] ]--return (dropExtension file ++ matrixNumber) | |
| :lowgl-0.3.1.1/Graphics/GL/Low/Framebuffer.hs | |
| 134;6 9: rbo <- return (RBO n) | |
| :lowgl-0.3.1.1/Graphics/GL/Low/Texture.hs | |
| 65;6 9: tex <- return (Tex2D n) | |
| 87;5 9: cm <- return (CubeMap n) | |
| 113;6 9: tex <- return (Tex2D n) | |
| 127;6 9: tex <- return (CubeMap n) | |
| :LslPlus-0.4.3/src/Language/Lsl/Sim.hs | |
| 286;34 9: InvObject links <- return $ inventoryItemData item | |
| 695;40 9: Just (Attachment k attachPoint) <- return attachment | |
| 1125;23 9: result <- return $ findTextureAsset id | |
| 2036;19 9: Just event <- return mevent | |
| 2046;19 9: Just event <- return mevent | |
| 2055;19 9: Just event <- return mevent | |
| 2064;19 9: Just event <- return mevent | |
| 2072;19 9: do Just event <- return mevent | |
| 2083;19 9: do Just event <- return mevent | |
| 2197;19 9: do Just event <- return mevent | |
| 3000;23 9: (y:ys') <- return ys | |
| 3282;9 9: m <- return . M.fromList =<< mapM ( \ (k,pos) -> if k `S.member` keysFromBefore | |
| 3648;54 9:-- Just i <- return $ elemIndex pk links | |
| :lucienne-0.0.2/Lucienne/Main.hs | |
| 30;15 9: serverConfig <- return $ nullConf { port = applicationPort args } | |
| :Lucu-0.7.0.3/ImplantFile.hs | |
| 81;34 9: do (opts, sources, errors) <- return . getOpt Permute options =<< getArgs | |
| :macho-0.22/src/Data/Macho.hs | |
| 182;13 9: reader <- return $ macho_reader magic | |
| 204;16 9: lc <- return $ runGet (getLoadCommand cmd mr lcdata fl mh) (L.fromChunks [lcdata]) | |
| 439;14 9: relocs <- return $ runGet (sequence (replicate nreloc (getRel mr mh))) $ L.fromChunks [B.drop reloff fl] | |
| 443;14 9: sectype <- return $ sectionType flags | |
| 444;14 9: userattrs <- return $ sectionUserAttribute flags | |
| 445;14 9: sysattrs <- return $ sectionSystemAttribute flags | |
| 465;14 9: relocs <- return $ runGet (sequence (replicate nreloc (getRel mr mh))) $ L.fromChunks [B.drop reloff fl] | |
| 470;14 9: sectype <- return $ sectionType flags | |
| 471;14 9: userattrs <- return $ sectionUserAttribute flags | |
| 472;14 9: sysattrs <- return $ sectionSystemAttribute flags | |
| 576;19 9: modules <- return $ B.unpack $ B.take ((nmodules `div` 8) + (nmodules `mod` 8)) $ B.drop modules_offset lc | |
| 772;12 9: strsect <- return $ B.take strsize $ B.drop stroff fl | |
| 807;26 9: iinit <- return (iinit_iterm .&. 0x0000ffff) | |
| 808;26 9: iterm <- return $ (iinit_iterm .&. 0xffff0000) `shiftR` 16 | |
| 810;26 9: ninit <- return (ninit_nterm .&. 0x0000ffff) | |
| 811;26 9: nterm <- return $ (ninit_nterm .&. 0xffff0000) `shiftR` 16 | |
| 837;26 9: iinit <- return (iinit_iterm .&. 0x0000ffff) | |
| 838;26 9: iterm <- return $ (iinit_iterm .&. 0xffff0000) `shiftR` 16 | |
| 840;26 9: ninit <- return (ninit_nterm .&. 0x0000ffff) | |
| 841;26 9: nterm <- return $ (ninit_nterm .&. 0xffff0000) `shiftR` 16 | |
| 958;19 9: rs_pcrel <- return $ bitfield mr 1 1 r_address == 1 | |
| 959;19 9: rs_length <- return $ 2 ^ bitfield mr 2 2 r_address | |
| 960;19 9: rs_type <- return $ flip r_type (mh_cputype mh) $ bitfield mr 4 4 r_address | |
| 961;19 9: rs_address <- return $ bitfield mr 8 24 r_address | |
| 962;19 9: rs_value <- return $ fromIntegral r_value | |
| 965;21 9: ri_address <- return $ fromIntegral r_address | |
| 966;21 9: ri_symbolnum <- return $ bitfield mr 0 24 r_value | |
| 967;21 9: ri_pcrel <- return $ bitfield mr 24 1 r_value == 1 | |
| 968;21 9: ri_length <- return $ 2 ^ bitfield mr 25 2 r_value | |
| 969;21 9: ri_extern <- return $ bitfield mr 27 1 r_value == 1 | |
| 970;21 9: ri_type <- return $ flip r_type (mh_cputype mh) $ bitfield mr 28 4 r_value | |
| 994;19 9: toc <- return $ runGet (sequence (replicate ntoc (getTOC mr))) $ L.fromChunks [B.drop tocoff fl] | |
| 1003;19 9: extrefsyms <- return $ runGet (sequence (replicate nextrefsyms (getWord32 mr))) $ L.fromChunks [B.drop extrefsymoff fl] | |
| 1006;19 9: indirectsyms <- return $ runGet (sequence (replicate nindirectsyms (getWord32 mr))) $ L.fromChunks [B.drop indirectsymoff fl] | |
| 1009;19 9: extrels <- return $ runGet (sequence (replicate nextrel (getRel mr mh))) $ L.fromChunks [B.drop extreloff fl] | |
| 1012;19 9: locrels <- return $ runGet (sequence (replicate nlocrel (getRel mr mh))) $ L.fromChunks [B.drop locreloff fl] | |
| 1046;26 9: name <- return $ C.unpack $ nullStringAt name_offset lc | |
| :marquise-4.0.0/src/MarquiseDaemon.hs | |
| 106;15 9: cacheFile' <- return $ case cacheFile of | |
| :mediawiki2latex-7.9.0.1/src/Compiler.hs | |
| 390;10 9: dd <- return $ | |
| 393;11 9: lll <- return $ | |
| 401;20 9: (trda, trst) <- return | |
| :mediawiki2latex-7.9.0.1/src/LatexRenderer.hs | |
| 455;9 9: r <- return $ | |
| 475;13 9: mystr <- return $ | |
| :mediawiki2latex-7.9.0.1/src/UrlAnalyse.hs | |
| 129;9 9: x <- return . toText $ h | |
| 145;9 9: x <- return . toText $ h | |
| 164;11 9: lll <- return (seq ll ll) | |
| 173;11 9: lll <- return (seq ll ll) | |
| 184;11 9: lll <- return (seq ll ll) | |
| 208;17 9: l <- return $ splitOn "/" $ (unify (url_path u)) | |
| 223;17 9: l <- return $ splitOn "/" $ (unify (url_path u)) | |
| :MFlow-0.4.6.0/src/MFlow/Forms.hs | |
| 836;7 10: rus <- return . tuser =<< gets mfToken | |
| :MFlow-0.4.6.0/src/MFlow.hs | |
| 423;5 9: t <- return . calendarTimeToString =<< toCalendarTime =<< getClockTime | |
| :Mhailist-0.0/Mhailist/Receive.hs | |
| 63;30 9: (addressees, msg) <- return $ | |
| :mi-0.0.1/src/Language/MI/TH.hs | |
| 118;7 9: fn <- return $ nameBase $ funcname $ tof $ toFuncD funcdef | |
| 120;12 9: changed <- return $ trans funcdef (fn:funcs) | |
| 122;11 9: funcds <- return $ tof $ toFuncD changed | |
| 124;6 9: t <- return $ mkExplicitFunc (namechange (mkName fn) funcds) funcs | |
| 126;8 9: imp <- return $ toFuncD $ mkimpfunc fn dic funcds | |
| :Michelangelo-0.2.4.0/src/Graphics/Michelangelo/Utils.hs | |
| 73;20 9:-- fileNamesExts <- return (map (++".tga") fileNames) | |
| :MiniAgda-0.2014.9.12/TypeChecker.hs | |
| 159;5 9: te <- return $ teleToType tel te | |
| 160;5 9: ee <- return $ teleLam tel ee | |
| 956;5 9: te <- return $ teleToType tel te | |
| 957;5 9: ee <- return $ teleLam tel ee | |
| :MissingH-1.4.0.0/src/Data/List/Utils.hs | |
| 435;15 9: (x, g') <- return $ splitAt count g | |
| :mmorph-1.0.6/src/Control/Monad/Morph.hs | |
| 371;9 9:> = do x <- return (runIdentity m) | |
| :mmtl-0.1/Control/Monad/State/Lazy.hs | |
| 255;36 9:-- > (newTable, newPos) <- return (nNode x table) | |
| :mmtl-0.1/Control/Monad/State/Strict.hs | |
| 254;36 9:-- > (newTable, newPos) <- return (nNode x table) | |
| :mole-0.0.3/src/Data/Mole/Server.hs | |
| 29;15 9: config <- return emptyConfig :: IO (SC.Config Snap ()) | |
| :monad-statevar-0.1/test/Main.hs | |
| 86;6 9: 9 <- return $ runST $ do | |
| 100;7 9: () <- return $ runST $ newSTRef 0 >>= testStateVar | |
| 101;7 9: () <- return $ L.runST $ L.newSTRef 0 >>= testStateVar | |
| :monads-fd-0.2.0.0/Control/Monad/State/Lazy.hs | |
| 101;36 9:-- > (newTable, newPos) <- return (nNode x table) | |
| :monads-fd-0.2.0.0/Control/Monad/State/Strict.hs | |
| 101;36 9:-- > (newTable, newPos) <- return (nNode x table) | |
| :monads-tf-0.1.0.2/Control/Monad/State/Lazy.hs | |
| 101;36 9:-- > (newTable, newPos) <- return (nNode x table) | |
| :monads-tf-0.1.0.2/Control/Monad/State/Strict.hs | |
| 101;36 9:-- > (newTable, newPos) <- return (nNode x table) | |
| :mp-0.2.2/src/Mp/UI/Menu.hs | |
| 63;9 9: menu <- return m1 <++> return m2 <++> return m3 <++> return m4 <++> return m5 | |
| :mp-0.2.2/src/Mp/UI/StatusBar.hs | |
| 66;11 9: status <- return left <++> return fill <++> return right | |
| :mtl-2.2.1/Control/Monad/State/Lazy.hs | |
| 102;36 9:-- > (newTable, newPos) <- return (nNode x table) | |
| :mtl-2.2.1/Control/Monad/State/Strict.hs | |
| 102;36 9:-- > (newTable, newPos) <- return (nNode x table) | |
| :mtl-tf-0.1/Control/Monad/State/Lazy.hs | |
| 283;36 9:-- > (newTable, newPos) <- return (nNode x table) | |
| :mtl-tf-0.1/Control/Monad/State/Strict.hs | |
| 282;36 9:-- > (newTable, newPos) <- return (nNode x table) | |
| :music-preludes-1.9.0/src/Music/Prelude/CmdLine.hs | |
| 164;16 9: newScore <- return $ if isNotExpression code | |
| :myTestlll-1.0.0/HSoM/Monads.lhs | |
| 319;5 9:do x <- return a ; k x = k a | |
| :mzv-0.1.0.2/src/Control/Monad/State/Lazy.hs | |
| 276;36 9:-- > (newTable, newPos) <- return (nNode x table) | |
| :mzv-0.1.0.2/src/Control/Monad/State/Strict.hs | |
| 264;36 9:-- > (newTable, newPos) <- return (nNode x table) | |
| :neat-0.1.0/Main.hs | |
| 27;17 9: result <- return $ parse f (takeFileName pathIn) string | |
| :neil-0.10/src/Cabal.hs | |
| 64;8 9: got <- return $ take (length require - 1) got ++ [last got] -- drop everything between script/wget | |
| 134;16 9: src <- return $ filter (/= '\r') src -- filter out \r, due to CPP bugs | |
| 135;16 9: src <- return $ fixFileLinks $ fixHashT src | |
| :neil-0.10/src/Paper/Graph.hs | |
| 25;8 9: res <- return [(date a,b,c) | s <- lines src, not $ null s, let (a,b,c) = read s, b `elem` files] | |
| :neil-0.10/src/Paper/Make.hs | |
| 61;6 9: s <- return $ filter ((==) ('.':ext) . takeExtension) s | |
| :neil-0.10/src/Paper/Sync.hs | |
| 17;11 9: xs <- return [dir </> x | x <- xs, not $ all (== '.') x] | |
| :neil-0.10/src/Paper/Util/FileData.hs | |
| 29;24 9: (explicit,implicit) <- return (concat explicit, concat implicit) | |
| 62;10 9: files <- return $ filter ((==) ".tex" . takeExtension) files | |
| :neil-0.10/src/Travis.hs | |
| 54;8 9: src <- return $ takeWhile (isPrefixOf " ") $ drop 1 $ dropWhile (not . isPrefixOf "relevant") src | |
| :net-concurrent-0.1.0/src/Control/Concurrent/Network/Master.hs | |
| 56;12 9: mcntx <- return $ M { registry = reg } | |
| 63;20 9: mymcntx <- return $ mcntx { slaveid = slaveid', numslaves = n } | |
| 121;16 9: val <- return $ reg ! name | |
| 153;24 9: val <- return $ reg ! name | |
| :net-concurrent-0.1.0/src/Control/Concurrent/Network/Process.hs | |
| 84;20 9: (acts, _, msgs) <- return $ getOpt RequireOrder options args | |
| :network-minihttp-0.2/Network/MiniHTTP/URL.hs | |
| 282;8 9: mhost <- return $ unsafePerformIO $ handle (const $ return Nothing) $ do | |
| :network-transport-tcp-0.5.1/tests/TestTCP.hs | |
| 116;13 9: True <- return $ addr == theirAddr | |
| 119;13 9: True <- return $ addr' == theirAddr | |
| 136;13 9: True <- return $ addr == theirAddr | |
| 139;13 9: True <- return $ cid == cid' | |
| 142;13 9: True <- return $ addr' == theirAddr | |
| 217;13 9: True <- return $ addr == theirAddr | |
| 220;13 9: True <- return $ cid' == cid | |
| 239;13 9: True <- return $ addr == theirAddr | |
| 242;13 9: True <- return $ cid' == cid | |
| 245;13 9: True <- return $ cid'' == cid | |
| 248;13 9: True <- return $ addr' == theirAddr | |
| 601;15 9: True <- return $ connId == connId' | |
| 680;11 9: True <- return $ connId == connId' | |
| :network-transport-tests-0.2.3.0/src/Network/Transport/Tests/Traced.hs | |
| 13;15 9:-- > Left x <- return (Left 1 :: Either Int Int) | |
| 15;15 9:-- > Right y <- return (Left 2 :: Either Int Int) | |
| 32;14 9:-- > Left x <- return (Left 1 :: Either Int Int) | |
| 33;14 9:-- > True <- return (x == 3) | |
| :network-transport-tests-0.2.3.0/src/Network/Transport/Tests.hs | |
| 82;55 9: Received cid' [reply] <- receive endpoint ; True <- return $ cid == cid' && reply == msg | |
| 91;51 9: ConnectionClosed cid' <- receive endpoint ; True <- return $ cid == cid' | |
| 476;11 9: True <- return $ testStreams ms [ [ ConnectionClosed cid2 ] | |
| 512;59 9: ConnectionOpened cid _ addr <- receive endpoint ; True <- return $ addr == address endpoint | |
| 516;57 9: Received cid' ["ping"] <- receive endpoint ; True <- return $ cid == cid' | |
| 520;53 9: ConnectionClosed cid' <- receive endpoint ; True <- return $ cid == cid' | |
| 564;9 9: True <- return $ events1 == replicate numPings ["pingA"] | |
| 565;9 9: True <- return $ events2 == replicate numPings ["pingB"] | |
| 602;43 9: TransportError ConnectFailed _ <- return r | |
| 624;75 9: ConnectionOpened cid ReliableOrdered addr <- receive endpoint ; True <- return $ addr == theirAddr | |
| 625;55 9: ConnectionClosed cid' <- receive endpoint ; True <- return $ cid == cid' | |
| 632;75 9: ConnectionOpened cid ReliableOrdered addr <- receive endpoint ; True <- return $ addr == theirAddr | |
| 633;56 9: Received cid' ["ping"] <- receive endpoint ; True <- return $ cid == cid' | |
| 638;56 9: ConnectionClosed cid'' <- receive endpoint ; True <- return $ cid == cid'' | |
| 639;91 9: ErrorEvent (TransportError (EventConnectionLost addr') _) <- receive endpoint ; True <- return $ addr' == theirAddr | |
| 671;75 9: ConnectionOpened cid ReliableOrdered addr <- receive endpoint ; True <- return $ addr == theirAddr | |
| 672;56 9: Received cid' ["pong"] <- receive endpoint ; True <- return $ cid == cid' | |
| 712;74 9: ConnectionOpened cid1 ReliableOrdered addr <- receive endpoint ; True <- return $ addr == theirAddr1 | |
| 717;75 9: ConnectionOpened cid2 ReliableOrdered addr' <- receive endpoint ; True <- return $ addr' == theirAddr2 | |
| 718;55 9: Received cid2' ["ping"] <- receive endpoint ; True <- return $ cid2' == cid2 | |
| 731;9 9: True <- return $ expected `elem` permutations evs | |
| 758;74 9: ConnectionOpened cid ReliableOrdered addr <- receive endpoint2 ; True <- return $ addr == theirAddr | |
| 759;55 9: Received cid' ["pong"] <- receive endpoint2 ; True <- return $ cid == cid' | |
| :NonEmpty-0.1/Data/List/NonEmpty.hs | |
| 5;30 9:listToNonEmpty s = do { (h:t) <- return s; return $ NonEmpty { neHead = h, neTail = t } } | |
| :nsis-0.3/Development/NSIS/Sugar.hs | |
| 848;6 9: v <- return (return $ Value $ val v :: Exp Int) | |
| 1145;7 9: as <- return $ foldl f Nothing as | |
| :nsis-0.3/Main.hs | |
| 50;10 9: names <- return $ if null names then map fst examples else names | |
| :Obsidian-0.4.0.0/Obsidian/Run/CUDA/Exec.hs | |
| 398;10 9: props <- return . csProps =<< get | |
| :olwrapper-0.4.1/wrapper/OpenLayers/Func.hs | |
| 93;12 9: sources <- return $ zipWith getVectorFeatureAt ( vectors) [ 0 | x <- [0..(Prelude.length features)-1]] | |
| :omega-1.5.2/Narrow.hs | |
| 548;23 9: do { newTerm <- return(varWild vv) | |
| :open-pandoc-1.5.1.1/src/Text/Pandoc/Readers/RST.hs | |
| 650;12 9: colLines <- return [] -- TODO | |
| :open-witness-0.3.1/Data/OpenWitness.hs | |
| 109;12 9: key <- return ((showLoc l) ++ "/" ++ (show rnd)); | |
| 110;16 9: keyExpr <- return (LitE (StringL key)); | |
| :OpenAFP-Utils-1.4.1.3/afp-dump.hs | |
| 67;25 9: (optsIO, rest, errs) <- return . getOpt Permute options $ procArgs args | |
| :OpenAFP-Utils-1.4.1.3/afp-replace.hs | |
| 231;27 9: (optsIO, _rest, _errs) <- return . getOpt Permute options $ procArgs args | |
| :OpenAFP-Utils-1.4.1.3/afp-udcfix.hs | |
| 427;25 9: (optsIO, rest, errs) <- return . getOpt Permute options | |
| :OpenAL-1.7.0.4/src/Sound/OpenAL/AL/Buffer.hs | |
| 128;7 9: raw <- return nullPtr -- ToDo: AL_DATA query missing!!! | |
| :OpenCLWrappers-0.1.0.3/System/OpenCL/Wrappers/Utils.hs | |
| 62;6 9: c <- return undefined | |
| 64;6 9: _ <- return (c:a) | |
| :OpenGLRaw-3.2.0.0/RegistryProcessor/src/Registry.hs | |
| 278;28 9: c <- return [x | GLXElement x <- xs] | |
| :openssl-createkey-0.1/OpenSSL/CreateKey.hs | |
| 22;10 9: cfile <- return (bfp++".public.cert") | |
| 23;10 9: sfile <- return (bfp++".secret.key") | |
| 52;8 9: cfile <- return (fp++".public.cert") | |
| 53;8 9: sfile <- return (fp++".secret.key") | |
| :optimusprime-0.0.1.20091117/Optimus/CallGraph.hs | |
| 102;13 9: g' <- return . concat . intersperse " " $ g : (map (\x -> fromMaybe "_" (return . show . snd =<< x)) $ bs) | |
| :orc-1.2.1.4/src/Examples/test.hs | |
| 74;12 9: (n,True) <- return (x, x `mod` y /= 0) | |
| :orchid-0.0.8/src/Network/Orchid/Core/Liaison.hs | |
| 63;18 9: (body, enc) <- return $ case b of | |
| :pandoc-1.17.0.3/src/Text/Pandoc/Readers/RST.hs | |
| 900;12 9: colLines <- return [] -- TODO | |
| :pandoc-1.17.0.3/src/Text/Pandoc/Writers/FB2.hs | |
| 373;6 9: c <- return . el "emphasis" =<< cMapM toXml caption | |
| 477;11 9: htmlMath <- return . writerHTMLMathMethod . writerOptions =<< get | |
| :papillon-0.1.0.2/src/Text/Papillon/Parser.hs | |
| 1855;93 9: b1437_469 <- return (((||) <$> isAlphaNum <*> (`elem` "_'")) c1616_145) | |
| 2325;94 9: b1508_595 <- return ((`elem` opChars) c1617_594) | |
| 2332;95 9: b1510_599 <- return ((`elem` opChars) c1618_598) | |
| 2346;81 9: b1513_605 <- return ((`notElem` "\\'") c1619_604) | |
| 2399;95 9: b1523_621 <- return (isDigit c1620_620) | |
| 2472;78 9: b1534_641 <- return (isUpper c1621_640) | |
| 2478;92 9: b1536_645 <- return (((||) <$> isAlphaNum <*> (`elem` "_'")) c1622_644) | |
| 2485;78 9: b1538_649 <- return (((||) <$> isLower <*> (== '_')) c1623_648) | |
| 2491;92 9: b1540_653 <- return (((||) <$> isAlphaNum <*> (`elem` "_'")) c1624_652) | |
| 2507;82 9: b1544_659 <- return ((`notElem` "\"\\") c1625_658) | |
| 2571;97 9: b1554_677 <- return (isHexDigit c1626_676) | |
| 2578;80 9: b1556_681 <- return ((`elem` " \t") c1627_680) | |
| 2595;81 9: b1561_685 <- return ((`elem` " \t") c1628_684) | |
| 2633;99 9: b1569_695 <- return ((/= '\n') c1629_694) | |
| :paragon-0.1.28/src/Language/Java/Paragon/TypeCheck/Constraints.hs | |
| 65;7 9: xs'' <- return $ partition fst xs' | |
| 76;7 9: xs'' <- return $ filter fst xs' | |
| :paragon-0.1.28/src/Language/Java/Paragon/TypeCheck/Monad.hs | |
| 1297;10 9: wcs <- return [(p, q) | (LRT _ p q, _) <- cs] | |
| 1299;13 9: cvarsm <- return (foldl linker Map.empty cvars) | |
| 1300;14 9: csubsts <- return (Map.foldlWithKey (\cs' x pxs -> foldl (\cs'' px-> (substitution x px cs'')) cs' pxs) wcs cvarsm) | |
| :parsec-trace-0.0.0.2/src/Text/Parsec/Trace/Tree.hs | |
| 80;11 9: result <- return . runIdentity $ runPT myparserWithState (MyState 0 T.initialTraceTree) "" text | |
| :PartialTypeSignatures-0.1.0.1/PartialTypeSigs.hs | |
| 131;37 9: VarE (Name (OccName k) _) : args <- return $ reverse (unappsErev call) | |
| :pcap-0.4.5.2/Network/Pcap/Base.hsc | |
| 411;12 9: l <- return (#size struct sockaddr) :: IO CUChar | |
| :pec-0.2.3/src/PecGen.hs | |
| 45;9 9: m1 <- return $ desugar m0 | |
| 50;8 9: m <- return $ hModule (dir args) cnts m1 | |
| :pecoff-0.11/src/Data/Pecoff.hs | |
| 259;26 9: pr <- return $ pecoffReader magic | |
| 364;23 9: name <- return $ runGet getSectionName $ L.fromChunks[full_name] | |
| :peggy-0.3.2/Text/Peggy/Parser.hs | |
| 112;78 9: return (v1 : v2)) <|> (do v1 <- return () | |
| 151;187 9: return (\v999 -> v1 (Optional v999)))) <|> (do v1 <- return () | |
| :permutation-0.5.0.5/lib/Data/Permute/MPermute.hs | |
| 266;15 9: valid <- return $ i' >= 0 && i' < n | |
| :persistent-sqlite-2.5.0.1/Database/Sqlite.hs | |
| 235;37 9: error <- return $ decodeError error' | |
| :pianola-0.1.1/src/Pianola/Model/Swing.hs | |
| 479;13 9: Label {} <- return . cType $ ref | |
| :pianola-0.1.1/tests/tests-pianola.hs | |
| 118;25 9: Table {} <- return . cType $ g | |
| :pointless-rewrite-0.0.3/src/Transform/Rewriting.hs | |
| 231;13 9: Just (x,l) <- return $ evalRWST (s t e) [0] (Dyn (Pf t) e) | |
| :polh-lexicon-0.2.2/src/NLP/Polh/Binary.hs | |
| 243;9 9: keys <- return $ case D.lookup (T.unpack x) fm of | |
| :portaudio-0.2.4/src/Sound/PortAudio/Base.hsc | |
| 433;11 9: ep <- return $ #{ptr PaHostErrorInfo, errorText} p | |
| :pqueue-mtl-1.0.7/Data/Queue/FibQueue.hs | |
| 44;42 9:extractFF f = do FF rk (RkT _ x ts : tss) <- return f | |
| :print-debugger-1.1.9/src/Debug/Print/StackTraceDebug.hs | |
| 26;50 9:debugTraceIO message = do -- Warning: "callStacks <- return(getCallStack (?loc))" cannot be replaced with "let callStacks = getCallStack (?loc)" because doing so would mess up the call stack. | |
| 27;13 9: callStacks <- return(getCallStack (?loc)) -- returns [(String, SrcLoc)] | |
| 62;44 9: else do -- Warning: "callStacks <- return(getCallStack (?loc))" cannot be replaced with "let callStacks = getCallStack (?loc)" because doing so would mess up the call stack. | |
| 63;30 9: callStacks <- return(getCallStack (?loc)) -- returns [(String, SrcLoc)] | |
| :Pugs-6.2.13.20150815/src/Pugs/Bind.hs | |
| 252;16 9: boundScalar <- return $ defaultScalar `zip` (givenInvs ++ givenArgs) -- put, uh, something in $_ | |
| :Pugs-6.2.13.20150815/src/Pugs/Parser/Unsafe.hs | |
| 69;12 9: subCode <- return $! unsafePerformIO $! runEvalIO env $! do | |
| :Pugs-6.2.13.20150815/src/Pugs/Parser/Util.hs | |
| 68;11 9: newPad <- return $! unsafePerformSTM $! do | |
| :Pugs-6.2.13.20150815/src/Pugs/Parser.hs | |
| 2089;34 9: foundInGlobal <- return $! unsafePerformSTM $! do | |
| :putlenses-0.1.3/src/Generics/Putlenses/TH.hs | |
| 145;3 9: m <- return $ mkName "m" | |
| 146;7 9: monad <- return $ mkName "Monad" | |
| :pyffi-0.4.0.2/Python.hs | |
| 172;6 9: y <- return (unpack . encode $ x) | |
| 188;8 9: key <- return $ hash s | |
| :pyfi-0.4.0.4/Python.hs | |
| 173;6 9: y <- return . unpack . encode $ x | |
| 189;8 9: key <- return $ hash s | |
| :qc-oi-testgenerator-1.2.0.3/Test/OITestGenerator.hs | |
| 208;32 9: axtp <- return_type_of_axiom axnm | |
| 409;37 9:is_applicable ax (argi, opn) = do xt <- return_type_of_axiom ax | |
| 417;32 9:is_applicable_Op ax opn = do xt <- return_type_of_axiom ax | |
| :qed-0.0/src/Proof/QED/Type.hs | |
| 71;6 9: x <- return $ f x | |
| 88;16 9: Proof proof <- return $ do | |
| :qed-0.0/src/Proof/QED.hs | |
| 328;6 9: p <- return $ simplifyProp p | |
| :rbr-0.8.6/src/RBR.lhs | |
| 43;31 9: case non of [] -> do ss <- return . map castToNuc =<< hReadFasta stdin | |
| :react-flux-1.0.7/example/todo/TodoStore.hs | |
| 37;17 9: newTodos <- return $ case action of | |
| :reactive-banana-1.1.0.1/src/Reactive/Banana/Test.hs | |
| 72;8 9: bs1 <- return $ interpretModel f (singletons xs) | |
| :reasonable-lens-0.2.1.1/src/Control/Lens/TH.hs | |
| 27;7 9: name <- return $ getFuncName v | |
| 31;14 9: funName <- return $ mkName nm | |
| :regex-pcre-0.94.4/Text/Regex/PCRE/Wrap.hsc | |
| 265;18 9: pairs <- return . toPairs =<< mapM (peekElemOff ovec) [0 .. ((pairsSet*2)-1)] | |
| 294;29 9: pairs <- return . toPairs =<< mapM (peekElemOff ovec) [0 .. ((pairsSet*2)-1)] | |
| 331;24 9: pairs <- return . toPairs =<< mapM (peekElemOff ovec) [0,1] | |
| :regex-pcre-builtin-0.94.4.8.8.35/Text/Regex/PCRE/Wrap.hsc | |
| 258;18 9: pairs <- return . toPairs =<< mapM (peekElemOff ovec) [0 .. ((pairsSet*2)-1)] | |
| 287;29 9: pairs <- return . toPairs =<< mapM (peekElemOff ovec) [0 .. ((pairsSet*2)-1)] | |
| 324;24 9: pairs <- return . toPairs =<< mapM (peekElemOff ovec) [0,1] | |
| :regex-posix-unittest-1.1/Main.hs | |
| 126;15 9: dataFileList <- return . lines =<< readFile =<< getDataFileName "test-manifest.txt" | |
| :regex-tdfa-1.2.2/Text/Regex/TDFA/TNFA.hs | |
| 607;8 9: mqt <- return . Just =<< getTrans qIn ( getE $ c ) | |
| :regex-tdfa-rc-1.1.8.3/Text/Regex/TDFA/TNFA.hs | |
| 604;8 9: mqt <- return . Just =<< getTrans qIn ( getE $ c ) | |
| :regex-tdfa-unittest-1.1/Main.hs | |
| 126;15 9: dataFileList <- return . lines =<< readFile =<< getDataFileName "test-manifest.txt" | |
| :relative-date-0.0.1/Data/DateTime/Parser.hs | |
| 105;7 9: l' <- return $ case l of {Nothing -> Nothing; (Just (a,_)) -> Just a} | |
| 114;15 9: a' <- return $ read a | |
| :rethinkdb-wereHamster-1.8.0.5/Database/RethinkDB/Time.hs | |
| 135;17 9: (h, _:m) <- return $ break (==':') tz' | |
| 136;33 9: ([(hh, "")], [(mm, "")]) <- return $ (reads h, reads m) | |
| :rex-0.5.1/Text/Regex/PCRE/Precompile.hs | |
| 47;8 9: len <- return . fromIntegral =<< (peek res :: IO CSize) | |
| :riot-1.20080618/Riot/RiotMain.hs | |
| 156;6 9: s <- return $ UI.set_topinfo s topinfo | |
| 157;6 9: s <- return $ UI.set_entries s tt (Just fname) | |
| 158;6 9: s <- return $ UI.set_callbacks s do_save new_mboxentry | |
| 167;7 9: tt <- return $! tt -- Force load before initialising UI | |
| :riot-1.20080618/Riot/Style.hs | |
| 98;15 9: a2 <- return (uiattr_set a name attr) | |
| 104;7 9: bw <- return (p<length styles) | |
| :Rlang-QQ-0.3.1.0/src/RlangQQ/Internal.hs | |
| 95;26 9: (variables, chanVars) <- return $ M.partitionWithKey (\k _ -> "hs_" `isPrefixOf` k) variables | |
| :rose-trie-1.0.0.1/src/Data/Tree/RoseTrie.hs | |
| 553;11 9: (a, l) <- return $ f $ st~>zipperSubRoseTrie~>leaf | |
| :rsagl-0.6.0.1/RSAGL/Modeling/Model.lhs | |
| 373;21 9: normal_vector <- return $ fromMaybe (degenerate_message) $ newell [a,b,c,d] | |
| :rtorrent-rpc-0.2.2.0/Network/RTorrent/File.hs | |
| 52;22 9: [hash, i] <- return $ splitOn ":f" str | |
| :rtorrent-rpc-0.2.2.0/Network/RTorrent/Peer.hs | |
| 59;22 9: [hash, s] <- return $ splitOn ":p" str | |
| :rtorrent-rpc-0.2.2.0/Network/RTorrent/Tracker.hs | |
| 48;22 9: [hash, i] <- return $ splitOn ":t" str | |
| :rvar-0.2.0.2/src/Data/RVar.hs | |
| 165;17 9:-- > (res,s) <- return (runState m s) | |
| :Salsa-0.2.0.2/Foreign/Salsa/Mono/CLRHost.hs | |
| 92;11 9: domain <- return "salsa" >>= flip withCString mono_jit_init | |
| :sarasvati-0.3.0.0/src/Sound/Sarasvati/Base.hs | |
| 42;10 9: smprate <- return $ confSampleRate conf | |
| 43;6 9: fpb <- return . Just $ confFramesPerBuffer conf | |
| 45;8 9: final <- return (Just $ swapMVar mstat Finished >> return ()) | |
| 75;17 9: (target, next) <- return $ wavSplitAt frameLen list | |
| :scenegraph-0.1.0.2/src/Graphics/SceneGraph/Textures.hs | |
| 21;17 9: fileNamesExts <- return (map (++".tga") fileNames) | |
| :scion-0.1.0.2/server/Main.hs | |
| 181;16 9: startupConfig <- return . fixConfig =<< foldrM ($) defaultStartupConfig opts | |
| :scotty-rest-0.1.0.0/src/Web/Scotty/Rest.hs | |
| 78;9 9: accept <- return . convertString . fromMaybe "*/*" =<< header "accept" | |
| :second-transfer-0.10.0.4/hs-src/SecondTransfer/Http2/Session.hs | |
| 1802;22 9: bs_chunks <- return $! bytestringChunk use_chunk_length data_to_send | |
| :second-transfer-0.10.0.4/hs-src/SecondTransfer/IOCallbacks/SocketServer.hs | |
| 64;16 9: addr_info1 <- return $ addr_info0 { | |
| 71;17 9: host_address <- return $ NS.addrAddress addr_info1 | |
| :second-transfer-0.10.0.4/tests/tests-hs-src/Tests/HTTP2Session.hs | |
| 280;9 9: seen <- return False | |
| 340;9 9: seen <- return False | |
| 434;9 9: seen <- return False | |
| :sednaDBXML-0.1.2.5/src/Database/SednaBindings.hs | |
| 150;22 9: response <- return $ getResponse numOfBytesRead size' | |
| :sensenet-0.1.0.0/main.hs | |
| 89;14 9: ihatethis <- return $ forever $ do | |
| :seqaid-0.4.0.0/Seqaid/Optim.hs | |
| 271;6 9:--- _ <- return $! x -- works as well?... | |
| 272;7 9: !_ <- return x -- magic! thank you!! | |
| :serversession-frontend-yesod-1.0/src/Web/ServerSession/Frontend/Yesod/Internal.hs | |
| 168;8 9: [raw] <- return $ do | |
| :SFML-2.3.2.2/src/SFML/Window/Window.hsc | |
| 178;15 9: result <- return . (/=0) =<< sfWindow_pollEvent wnd ptrEvt | |
| :shake-0.15.6/src/Development/Ninja/All.hs | |
| 37;10 9: rules <- return $ Map.fromList [r | r <- rules, BS.unpack (fst r) `elem` args] | |
| 60;17 9: needDeps <- return $ needDeps ninja -- partial application | |
| 61;15 9: phonys <- return $ Map.fromList phonys | |
| 62;16 9: singles <- return $ Map.fromList $ map (first filepathNormalise) singles | |
| 63;18 9: multiples <- return $ Map.fromList [(x,(xs,b)) | (xs,b) <- map (first $ map filepathNormalise) multiples, x <- xs] | |
| 64;14 9: rules <- return $ Map.fromList rules | |
| 147;11 9: xs <- return $ filter (`Map.member` builds) xs | |
| :shake-0.15.6/src/Development/Shake/Args.hs | |
| 127;9 9: errs <- return $ errs ++ flagsError ++ ["cannot mix " ++ a ++ " and " ++ b | a:b:_ <- | |
| :shake-0.15.6/src/Development/Shake/Command.hs | |
| 320;11 9: switch <- return $ case () of | |
| :shake-0.15.6/src/Development/Shake/Core.hs | |
| 547;10 9: e <- return $ ShakeException (last $ "Unknown call stack" : stk) stk e | |
| 675;12 9: bad <- return $ localTrackUsed \\ deps | |
| :shake-0.15.6/src/Development/Shake/Database.hs | |
| 195;28 9: (is, i) <- return $ Intern.add k is | |
| 205;18 9: stack <- return $ reverse $ map (maybe "<unknown>" (show . fst) . flip Map.lookup status) $ bad:xs | |
| 206;24 9: (tk, tname) <- return $ case Map.lookup bad status of | |
| 267;42 9: r <- return r{result=s} | |
| 460;8 9: bad <- return [(parent,key) | (parent, key) <- missing, isJust $ Intern.lookup key intern] | |
| 522;30 9: (mp1, stepId) <- return $ Intern.add stepKey mp1 | |
| :shake-0.15.6/src/Development/Shake/Pool.hs | |
| 44;70 9:dequeue (Queue [] (Right (Just t))) = Just $ do bs <- randomIO; (x,t) <- return $ removeTree bs t; return (x, Queue [] $ Right t) | |
| 138;9 9: todo <- return $ enqueue (void act) (todo s) | |
| 145;9 9: todo <- return $ enqueuePriority (void act) (todo s) | |
| :shake-0.15.6/src/Development/Shake/Progress.hs | |
| 232;39 9: ((secs,perc,debug), mealy) <- return $ runMealy mealy (t, p) | |
| :shake-0.15.6/src/General/Process.hs | |
| 177;29 9: dest <- return $ for dest $ \d -> case d of | |
| 187;29 9: dest <- return $ for dest $ \d -> case d of | |
| :shake-0.15.6/src/Run.hs | |
| 30;24 9: (prog,args) <- return $ | |
| :shake-0.15.6/src/Test/FilePattern.hs | |
| 170;20 9: (False, Walk _) <- return $ walk ["*.xml"] | |
| 171;20 9: (False, Walk _) <- return $ walk ["//*.xml"] | |
| 172;20 9: (False, Walk _) <- return $ walk ["**/*.xml"] | |
| 173;43 9: (False, WalkTo ([], [("foo",Walk _)])) <- return $ walk ["foo//*.xml"] | |
| 174;43 9: (False, WalkTo ([], [("foo",Walk _)])) <- return $ walk ["foo/**/*.xml"] | |
| 175;65 9: (False, WalkTo ([], [("foo",WalkTo ([],[("bar",Walk _)]))])) <- return $ walk ["foo/bar/*.xml"] | |
| 176;54 9: (False, WalkTo (["a"],[("b",WalkTo (["c"],[]))])) <- return $ walk ["a","b/c"] | |
| 178;57 9: (False, WalkTo ([],[("bar",Walk _),("baz",Walk _)])) <- return $ walk ["bar/*.xml","baz//*.c"] | |
| 179;57 9: (False, WalkTo ([],[("bar",Walk _),("baz",Walk _)])) <- return $ walk ["bar/*.xml","baz/**/*.c"] | |
| 180;29 9: (False, WalkTo ([], [])) <- return $ walk [] | |
| 181;19 9: (True, Walk _) <- return $ walk ["//"] | |
| 182;19 9: (True, Walk _) <- return $ walk ["**"] | |
| 183;21 9: (True, WalkTo _) <- return $ walk [""] | |
| :shake-0.15.6/src/Test/Type.hs | |
| 50;9 9: args <- return $ args \\ ["--sleep","--forward"] | |
| 78;17 9: opts <- return $ shakeOptions | |
| 81;17 9: opts <- return $ if forward then forwardOptions opts else opts | |
| :shakespeare-2.0.8.2/Text/Hamlet.hs | |
| 191;11 9: [fields] <- return [fields | RecC name fields <- cons, name == conName] | |
| :shakespeare-2.0.8.2/Text/Lucius.hs | |
| 197;19 9: (int, _):_ <- return $ readHex $ dropWhile (== '0') hex | |
| :shelly-1.6.6/src/Shelly.hs | |
| 773;7 9: mval <- return . fmap T.pack . lookup (T.unpack k) =<< gets sEnvironment | |
| :simseq-0.0/src/UnfoldMut.hs | |
| 134;11 9: (g,g') <- return . split =<< newStdGen | |
| :snaplet-environments-0.1.1/src/Snap/Snaplet/Environments.hs | |
| 37;7 9: mopt <- return . find (\a -> take 1 a == "@") =<< liftIO getArgs | |
| :snaplet-fay-0.3.3.13/src/Snap/Snaplet/Fay.hs | |
| 140;6 9: res <- return $ A.decode body >>= readFromFay | |
| :snaplet-redson-0.1.0.0/src/Snap/Snaplet/Redson/Snapless/CRUD.hs | |
| 167;8 9: newId <- return $ (BU.fromString . show) n | |
| :snaplet-redson-0.1.0.0/src/Snap/Snaplet/Redson.hs | |
| 414;26 9: patFunction <- return $ case mType of | |
| 419;26 9: searchType <- return $ case sType of | |
| :snaplet-tasks-0.1.2/src/Snap/Snaplet/Tasks/Internal.hs | |
| 23;8 9: _args <- return . dropWhile ((/=) "T") =<< getArgs | |
| :snaplet-tasks-0.1.2/src/Snap/Snaplet/Tasks/Utils.hs | |
| 24;12 9: localIp <- return . rqLocalAddr =<< getRequest | |
| 25;12 9: requestIp <- return . rqRemoteAddr =<< getRequest | |
| :socket-0.6.0.1/src/System/Socket/Internal/Socket.hsc | |
| 126;4 9: u <- return undefined | |
| :socket-sctp-0.1.0.0/src/System/Socket/Protocol/SCTP/Internal.hsc | |
| 172;16 9: uaddr <- return undefined | |
| :source-code-server-2010.9.1/src/CodeMushu/Repo.hs | |
| 376;12 9: exit_code <- return_after 30 - unpack_repo repo cb p | |
| :Southpaw-0.1.0.2/lib/Southpaw/Michelangelo/Utils.hs | |
| 70;20 9:-- fileNamesExts <- return (map (++".tga") fileNames) | |
| :spacepart-0.1.0.0/test/Render.hs | |
| 92;20 9: window_size <- return . fromJust . mwindow_size =<< readIORef viewer_ref | |
| :spike-0.3/src/BrowseTreeOperations.hs | |
| 55;25 9: t0 <- return str | |
| :sr-extra-1.46.3.2/Extra/HughesPJ.hs | |
| 10;15 9: do columns <- return . fromMaybe 80 =<< getWidth | |
| :stack-1.1.2/src/Stack/New.hs | |
| 189;19 9: (year, _, _) <- return $ toGregorian . utctDay $ now | |
| :stack-1.1.2/test/integration/IntegrationSpec.hs | |
| 121;20 9: Just suffix <- return $ stripPrefix src srcfp | |
| :starrover2-0.1.1/src/SpaceState/Combat.hs | |
| 38;29 9: s' <- return $ | |
| :starrover2-0.1.1/src/Statistics.hs | |
| 15;10 9: (x, g') <- return $ randomR v g | |
| :stepwise-1.0.2/src/Control/Monad/Stepwise/Examples.hs | |
| 117;13 9:test5 = do x <- return 3 | |
| 138;30 9: u <- lazily $ do y <- return 2 | |
| :Strafunski-ATermLib-1.6.0.3/Data/ATerm/IO.hs | |
| 33;12 9: opts <- return $ parseOptions progName args | |
| 35;12 9: tin <- return . fromATerm . dehyphenAST . readATerm $ sin | |
| 37;12 9: sout <- return . toString (format opts) $ tout | |
| :Strafunski-Sdf2Haskell-1.0.0.2/generator/Sdf2Haskell.hs | |
| 73;12 9: opts <- return $ parseOptions progName args | |
| 76;12 9: sout <- return . toString progName (format opts) $ tout | |
| :Strafunski-StrategyLib-5.0.0.8/Data/Generics/Strafunski/StrategyLib/RefactoringTheme.hs | |
| 87;22 9: names <- return (freeNames declared referenced scope') | |
| 108;18 9: free <- return $ freeNames declared referenced abstrlist' | |
| 133;21 9: free <- return $ freeTypedNames declared referenced bound focus | |
| :StrategyLib-4.0.0.0/library/Data/Generics/Strafunski/StrategyLib/RefactoringTheme.hs | |
| 88;22 9: names <- return (freeNames declared referenced scope') | |
| 109;18 9: free <- return $ freeNames declared referenced abstrlist' | |
| 134;21 9: free <- return $ freeTypedNames declared referenced bound focus | |
| :streaming-commons-0.1.15.5/test/Data/Streaming/ZlibSpec.hs | |
| 99;21 9: deflated <- return $ deflateWithDict exampleDict raw | |
| 100;21 9: inflated <- return $ inflateWithDict (S.drop 1 exampleDict) deflated | |
| :strict-identity-0.1.0.0/src/Control/Monad/StrictIdentity.hs | |
| 35;6 9: w <- return $! f x y | |
| 36;6 9: j <- return $! h w z | |
| 37;8 9: res <- return $! g w j | |
| 50;10 9: x <- return $! ((x .&. 0x00000000FFFF0000) << 16 ) | |
| 52;10 10: x <- return $! ((x .&. 0x0000FF000000FF00 ) << 8 ) | |
| 54;9 10: x<- return $! (( x .&. 0x00F000F000F000F0 ) << 4 ) | |
| 56;9 11: x<- return $!((x .&. 0x0C0C0C0C0C0C0C0C )<< 2 ) | |
| 58;9 11: x<- return $! ( (x .&. 0x2222222222222222) << 1 ) | |
| :sunroof-compiler-0.2/Language/Sunroof/Compiler.hs | |
| 390;22 9: , Just c <- return $ Map.lookup n jsVars | |
| 391;20 9: , Just e' <- return $ Map.lookup n dbF | |
| :sunroof-compiler-0.2/Language/Sunroof/Types.hs | |
| 409;7 9:-- > x <- return $ "A" <> "B" | |
| :supero-3.0/Simplify.hs | |
| 67;7 9: xs <- return $ rebind v xs | |
| 69;8 9: ren <- return $ Map.fromList (zip (map fst xs) vs2) `Map.union` ren | |
| 83;16 9: ren <- return $ Map.fromList (zip vs vs2) `Map.union` ren | |
| 191;23 9: e3 <- return $ fuse look e2 | |
| 439;10 9: free2 <- return [Map.findWithDefault "_" x old | x <- free] | |
| :swapper-0.1/test/test.hs | |
| 47;19 9: x' <- return . getting (!!i) =<< readIORef x | |
| :syb-0.6/tests/Perm.hs | |
| 93;18 9: ske <- return $ fromConstr con | |
| 94;18 9: fs <- return $ gmapQ buildT' ske | |
| :tagged-th-0.1/Data/Proxy/TH/Aux.hs | |
| 48;4 9: s <- return $ trim s | |
| 49;9 9: (i, s) <- return $ | |
| :tagsoup-0.13.10/TagSoup/Benchmark.hs | |
| 129;7 9: () <- return x | |
| :tamarin-prover-0.8.6.3/Setup.hs | |
| 78;14 9: -- ver_line <- return "v0.1-42-gf9f4eb3-dirty" | |
| :tamarin-prover-term-0.8.5.1/Setup.hs | |
| 78;14 9: -- ver_line <- return "v0.1-42-gf9f4eb3-dirty" | |
| :tamarin-prover-theory-0.8.6.0/Setup.hs | |
| 78;14 9: -- ver_line <- return "v0.1-42-gf9f4eb3-dirty" | |
| :tamarin-prover-theory-0.8.6.0/src/Theory/Constraint/Solver/Contradictions.hs | |
| 127;15 9: [conc] <- return $ L.get rConcs ru | |
| 262;16 9: [p1,p2] <- return $ L.get rPrems ru | |
| 263;16 9: [conc] <- return $ L.get rConcs ru | |
| 295;12 9: [p1,p2] <- return $ L.get rPrems ru | |
| 296;12 9: [conc] <- return $ L.get rConcs ru | |
| 332;17 9: [sP_f, rQ_f] <- return $ L.get rPrems ruEMap | |
| 352;17 9: [f_p0, f_p1] <- return $ L.get rPrems ruDEMap | |
| 353;11 9: [f_c0] <- return $ L.get rConcs ruDEMap | |
| :tamarin-prover-theory-0.8.6.0/src/Theory/Constraint/Solver/Simplify.hs | |
| 203;44 9: && null [ () | t <- ts, FUnion _ <- return (viewTerm2 t) ] | |
| :tamarin-prover-theory-0.8.6.0/src/Theory/Tools/RuleVariants.hs | |
| 77;19 9: -- x <- return (emptySubst, Just substs) -- | |
| :tamarin-prover-utils-0.8.5.1/Setup.hs | |
| 78;14 9: -- ver_line <- return "v0.1-42-gf9f4eb3-dirty" | |
| :task-distribution-0.1.0.3/app/TestVisitCalculation.hs | |
| 17;9 9: visits <- return $ calculateVisits $ BLC.lines contents | |
| :task-distribution-0.1.0.3/src/Control/Distributed/Task/Distribution/DataLocality.hs | |
| 26;16 9: mergedNodeIds <- return $ map fst $ reverse $ sortOn snd $ merge (matcher hosts) merger nodes hostsWithData | |
| :task-distribution-0.1.0.3/src/Control/Distributed/Task/Distribution/RunComputation.hs | |
| 69;31 9: (resultDef, resultProcessor) <- return $ buildResultDef resultSpec | |
| 119;15 9: absolute <- return $ map (prefix++) paths :: IO [String] | |
| :task-distribution-0.1.0.3/src/Control/Distributed/Task/Distribution/TaskDistribution.hs | |
| 275;16 9: taskTransport <- return $ TaskTransport masterProcess (TaskMetaData (taskDescription taskDef dataDefs slaveNode) slaveNode (serializeTime now)) preparedTaskDef dataDefs resultDef | |
| 281;11 9: hash <- return $ RemoteStore.calculateHash program | |
| :task-distribution-0.1.0.3/src/Control/Distributed/Task/TaskSpawning/BinaryStorage.hs | |
| 41;11 9: filePath <- return $ homeDir ++ "/" ++ (show fileHash) | |
| 48;10 9: homeDir <- return $ sysTempDir ++ "/temp-binary-storage/" | |
| :task-distribution-0.1.0.3/src/Control/Distributed/Task/TaskSpawning/SourceCodeExecution.hs | |
| 78;17 9: moduleFile <- return $ moduleTempDir </> moduleName ++ ".hs" | |
| :task-distribution-0.1.0.3/src/Control/Distributed/Task/Util/Logging.hs | |
| 35;8 9: h <- return $ L.setFormatter logHandler (L.simpleLogFormatter "[$time : $loggername : $prio] $msg") | |
| :TCache-0.12.0/Data/TCache/IndexQuery.hs | |
| 395;13 9: rxs <- return . map sel =<< return . catMaybes =<< mapM readDBRef xs | |
| 396;13 9: rys <- return . map sel' =<< return . catMaybes =<< mapM readDBRef ys | |
| :template-0.2.0.10/Data/Text/Template.hs | |
| 296;16 9: else do c <- return $! T.head s | |
| :tex2txt-0.1.0.0/Text/Tex2txt.hs | |
| 476;40 9: envT <- return $ | |
| 503;42 9: r <- return $ TexGroup (Start (sourceLine p) (sourceColumn p)) (Stop (sourceLine p2) (sourceColumn p2)) ("\\begin{" ++ tt ++ "}") (esp ++ "\\end{" ++ tt ++ "}") x sp | |
| 1108;34 9: Just (x,sp) <- return $ getCommandName xT | |
| 1164;27 9: Just (x,sp) <- return $ getCommandName xT | |
| 1222;89 9: Just (x,sp) <- return $ getCommandName ccc2 | |
| 1223;82 9: ccc2 <- return $ TexCommand (Start (sourceLine p) (sourceColumn p)) (Stop (sourceLine p2) (sourceColumn p2)) ("\\LET" ++ x) [] sp | |
| 1231;59 9: mode <- return "def" | |
| 1260;57 9: rt <- return $! TexNewCommand (Start (sourceLine p) (sourceColumn p)) (Stop (sourceLine p2) (sourceColumn p2)) ccc1 (read ccc2) ccc3 ccc4 sp | |
| 1267;59 9: mode <- return "def" | |
| 1292;57 9: rt <- return $! TexNewCommand (Start (sourceLine p) (sourceColumn p)) (Stop (sourceLine p2) (sourceColumn p2)) ccc1 (read ccc2) ccc3 ccc4 sp | |
| 1299;59 9: mode <- return "def" | |
| 1326;57 9: rt <- return $! TexNewEnvironment (Start (sourceLine p) (sourceColumn p)) (Stop (sourceLine p2) (sourceColumn p2)) ccc1 (read ccc2) ccc3 ccc4 ccc5 sp | |
| 1333;59 9: mode <- return "def" | |
| 1342;57 9: rt <- return $! TexDef (Start (sourceLine p) (sourceColumn p)) (Stop (sourceLine p2) (sourceColumn p2)) ccc1 ccc2 ccc3 sp | |
| 1390;90 9: Just (xx,sp) <- return $ getCommandName cmd | |
| 1487;57 9: rt <- return $! TexRegistry (Start (sourceLine p) (sourceColumn p)) (Stop (sourceLine p2) (sourceColumn p2)) cmd "count" (TexEmpty v) sp | |
| 1499;57 9: rt <- return $! TexRegistry (Start (sourceLine p) (sourceColumn p)) (Stop (sourceLine p2) (sourceColumn p2)) cmd "dimen" (TexEmpty v) sp | |
| 1511;57 9: rt <- return $! TexRegistry (Start (sourceLine p) (sourceColumn p)) (Stop (sourceLine p2) (sourceColumn p2)) cmd "skip" (TexEmpty v) sp | |
| 1523;57 9: rt <- return $! TexRegistry (Start (sourceLine p) (sourceColumn p)) (Stop (sourceLine p2) (sourceColumn p2)) cmd "token" (TexEmpty v) sp | |
| 1548;69 9: Just (xxx,sps) <- return $ getCommandName c | |
| 1550;57 9: br <- return $ TexBraces (Start (sourceLine p) (sourceColumn p)) (Stop (sourceLine p2) (sourceColumn p2)) "{" "}" ccc4 sp | |
| 1551;59 9: ccc5 <- return $ TexCommand (Start (sourceLine p) (sourceColumn p)) (Stop (sourceLine p2) (sourceColumn p2)) ('\\':xxx) [br] sps | |
| 1552;57 9: rt <- return $! TexNewCommand (Start (sourceLine p) (sourceColumn p)) (Stop (sourceLine p2) (sourceColumn p2)) ccc1 0 Nothing [ccc5] sp | |
| 1632;67 9: (true,false) <- return $ span (\tT-> not $ L.isSuffixOf "\\else" (texAsTxt tT)) t2 | |
| 1680;67 9: (true,false) <- return $ span (\tT-> not $ L.isSuffixOf "\\else" (texAsTxt tT)) t2 | |
| 1706;67 9: (true,false) <- return $ span (\tT-> not $ L.isSuffixOf "\\else" (texAsTxt tT)) t2 | |
| 1728;67 9: (true,false) <- return $ span (\tT-> not $ L.isSuffixOf "\\else" (texAsTxt tT)) t2 | |
| 1940;57 9: b <- return $ TexToken (Start (sourceLine pT) (sourceColumn pT)) (Stop (sourceLine p2) (sourceColumn p2)) (esp ++ ms) "" | |
| 2154;35 9: Just (x,sp) <- return $ getCommandName xT | |
| 2190;54 9: Just (x,sp) <- return $ getCommandName xTT | |
| :th-desugar-1.6/Language/Haskell/TH/Desugar/Util.hs | |
| 119;11 9: '(' : s1 <- return s | |
| 120;16 9: (commas, ")") <- return $ span (== ',') s1 | |
| 133;17 9: '(' : '#' : s1 <- return s | |
| 134;17 9: (commas, "#)") <- return $ span (== ',') s1 | |
| :ThreadObjects-0.0/Control/Concurrent/ThreadObject.lhs | |
| 168;25 9:> (value',returnValue) <- return (action value) | |
| :tip-lib-0.2.2/src/Tip/Pass/Induction.hs | |
| 22;17 9: do TyCon tc ts <- return t | |
| :tls-1.3.8/Tests/Certificate.hs | |
| 36;13 9: nsec <- return 0 | |
| :topkata-0.2.4/Topkata/Render.hs | |
| 25;8 9: --hit <- return False -- get (showHit state) | |
| :torrent-10000.0.0/src/Data/Torrent/Scrape.hs | |
| 39;32 9: [BDict dict'] <- return (Map.elems files) | |
| :toysolver-0.4.0/src/ToySolver/Arith/CAD.hs | |
| 196;4 9: p <- return $ P.reduce P.grevlex p gb | |
| 197;5 9: ss <- return $ Set.fromList ss | |
| 198;5 9: ss <- return $ ss `Set.intersection` computeSignSet m p | |
| 202;11 9: (p,ss) <- return $ (P.mapCoeff (/c) p, Set.map (\s -> s `Sign.div` Sign.signOf c) ss) | |
| 204;7 9: ss <- return $ Set.intersection ss ss_orig | |
| :toysolver-0.4.0/src/ToySolver/Arith/MIPSolverHL.hs | |
| 211;29 9: , Just (m, val) <- return (IM.lookup v tbl) | |
| :toysolver-0.4.0/src/ToySolver/Arith/Simplex2.hs | |
| 251;49 9: [(p - c) / (k - q) | Just (Delta c k, _) <- return lb, c < p, k > q] ++ | |
| 252;49 9: [(d - p) / (q - h) | Just (Delta d h, _) <- return ub, p < d, q > h] | |
| :toysolver-0.4.0/src/ToySolver/Data/MIP/LPFile.hs | |
| 139;8 9: bnds2 <- return $ Map.unionWith MIP.intersectBounds | |
| :toysolver-0.4.0/src/ToySolver/EUF/CongruenceClosure.hs | |
| 306;34 9: (a,b,a',b',classA,classB) <- return $ | |
| :toysolver-0.4.0/toysolver/toysolver.hs | |
| 147;38 9: [Const x .<=. v2 | MIP.Finite x <- return l] ++ | |
| 148;40 9: [v2 .<=. Const x | MIP.Finite x <- return u] | |
| :tpdb-1.2.0/src/TPDB/Convert.hs | |
| 38;14 9: [ arg ] <- return args | |
| :tracer-0.1/README.lhs | |
| 156;22 9:> x <- return $ 1 - n | |
| 157;22 9:> y <- return $ 2 * n | |
| 158;22 9:> t <- return $ x * y | |
| 160;22 9:> u <- return $ y - t | |
| 163;22 9:> v <- return $ t * x | |
| 166;22 9:> m <- return $ n * n | |
| 167;22 9:> o <- return $ m + m + u + v | |
| 194;21 9:> d <- return $ n + n | |
| :tracer-0.1/Debug/Tracer.hs | |
| 205;59 9: (TracerT x') <- return $ f v | |
| 224;46 9: (TracerT x') <- return $ f v | |
| :TrendGraph-0.1.0.1/Main.hs | |
| 47;31 9: timenum <- return $ timeListFromString times | |
| 58;18 9: timenum <- return $ timeListFromString times-} | |
| 60;16 9: point <- return $ points t-} | |
| :ttask-0.0.0.2/src/Data/TTask/File.hs | |
| 32;6 9: dir <- return . (++"/") =<< projectsDirectory | |
| 38;6 9: dir <- return . (++"/") =<< projectsDirectory | |
| :tttool-1.6.1/src/Commands.hs | |
| 331;28 9: , (idxstr:string:_) <- return $ wordsWhen (';'==) l | |
| 332;19 9: , Just idx <- return $ readMaybe idxstr | |
| :turtle-1.2.8/src/Turtle/Prelude.hs | |
| 1263;8 9: _:_ <- return (match pattern txt) | |
| 1284;11 9: txt':_ <- return (match pattern' txt) | |
| 1305;14 9: Right txt <- return (Filesystem.toText path) | |
| 1306;14 9: _:_ <- return (match pattern txt) | |
| :turtle-1.2.8/src/Turtle/Tutorial.hs | |
| 334;10 9:-- > do x <- return expr -- X=EXPR | |
| :twentefp-websockets-0.1.0.1/src/Network/WebSockets/Client.hs | |
| 97;17 9: Response _ _ <- return $ finishResponse protocol request response | |
| :unagi-chan-0.4.0.0/tests/UnagiBounded.hs | |
| 90;30 9: lengthEqualsBounds <- return True -- TODO get and check length from segSource arr, possible? | |
| :unamb-custom-0.13/UnambCustom/Unamb.hs | |
| 132;16 9: parententry <- return $! Map.lookup parentid livemap | |
| :uni-htk-2.2.1.2/HTk/Widgets/Editor.hs | |
| 95;7 9: tp <- return (Editor w) | |
| :uni-htk-2.2.1.2/HTk/Widgets/Scale.hs | |
| 88;7 9: sc <- return (Scale wid ref) | |
| :uni-uDrawGraph-2.2.1.3/UDrawGraph/Graph.hs | |
| 1177;20 9: atts <- return ([titleAttribute arcText]) | |
| :unicoder-0.4.1/unicoder.hs | |
| 49;28 9: (actions, args, errors) <- return . getOpt Permute options =<< getArgs | |
| :uniplate-1.6.12/Data/Generics/Uniplate/Internal/Data.hs | |
| 150;22 9: (hit,fol) <- return $ case res of | |
| :unix-2.7.2.0/System/Posix/SharedMem.hsc | |
| 53;15 9: do cflags0 <- return 0 | |
| 54;15 9: cflags1 <- return $ cflags0 .|. (if shmReadWrite flags | |
| 57;15 9: cflags2 <- return $ cflags1 .|. (if shmCreate flags then #{const O_CREAT} | |
| 59;15 9: cflags3 <- return $ cflags2 .|. (if shmExclusive flags | |
| 62;15 9: cflags4 <- return $ cflags3 .|. (if shmTrunc flags then #{const O_TRUNC} | |
| :unix-2.7.2.0/System/Posix/User.hsc | |
| 458;10 9: gecos <- return "" -- pw_gecos does not exist on android | |
| :uuagc-0.9.52.1/src/KennedyWarren.hs | |
| 178;35 9:toGVNontDependencyInfo ndi = do dg <- return $ ndgmDepGraph . ndimDepGraph $ ndi | |
| 198;36 9:toGVProdDependencyGraph pdg = do dg <- return $ pdgmDepGraph pdg | |
| :uuagc-0.9.52.1/src/Knuth1.hs | |
| 199;5 9: vs <- return $ Array.indices $ vertexOMap g | |
| 446;41 9: prodGraph <- return $ pdgmDepGraph pdg | |
| 514;40 9: prodGraph <- return $ pdgmDepGraph pdg | |
| :uuagc-0.9.52.1/src-generated/AbstractSyntaxDump.hs | |
| 53;32 9: (T_Child_vOut1 _lhsOpp) <- return (inv_Child_s2 sem arg1) | |
| 102;44 9: (T_Children_vOut4 _lhsOpp _lhsOppL) <- return (inv_Children_s5 sem arg4) | |
| 183;37 9: (T_Expression_vOut7 _lhsOpp) <- return (inv_Expression_s8 sem arg7) | |
| 232;35 9: (T_Grammar_vOut10 _lhsOpp) <- return (inv_Grammar_s11 sem arg10) | |
| 289;39 9: (T_Nonterminal_vOut13 _lhsOpp) <- return (inv_Nonterminal_s14 sem arg13) | |
| 340;49 9: (T_Nonterminals_vOut16 _lhsOpp _lhsOppL) <- return (inv_Nonterminals_s17 sem arg16) | |
| 421;45 9: (T_Pattern_vOut19 _lhsOcopy _lhsOpp) <- return (inv_Pattern_s20 sem arg19) | |
| 596;55 9: (T_Patterns_vOut22 _lhsOcopy _lhsOpp _lhsOppL) <- return (inv_Patterns_s23 sem arg22) | |
| 695;38 9: (T_Production_vOut25 _lhsOpp) <- return (inv_Production_s26 sem arg25) | |
| 750;48 9: (T_Productions_vOut28 _lhsOpp _lhsOppL) <- return (inv_Productions_s29 sem arg28) | |
| 831;32 9: (T_Rule_vOut31 _lhsOpp) <- return (inv_Rule_s32 sem arg31) | |
| 884;42 9: (T_Rules_vOut34 _lhsOpp _lhsOppL) <- return (inv_Rules_s35 sem arg34) | |
| 965;35 9: (T_TypeSig_vOut37 _lhsOpp) <- return (inv_TypeSig_s38 sem arg37) | |
| 1014;45 9: (T_TypeSigs_vOut40 _lhsOpp _lhsOppL) <- return (inv_TypeSigs_s41 sem arg40) | |
| :uuagc-0.9.52.1/src-generated/AG2AspectAG.hs | |
| 391;95 9: (T_Child_vOut1 _lhsOidCL _lhsOppCSF _lhsOppDL _lhsOppL _lhsOppLI _lhsOppR _lhsOprdInh) <- return (inv_Child_s2 sem arg1) | |
| 561;98 9: (T_Children_vOut4 _lhsOidCL _lhsOppCSF _lhsOppDL _lhsOppL _lhsOppLI _lhsOppR _lhsOprdInh) <- return (inv_Children_s5 sem arg4) | |
| 772;39 9: (T_Expression_vOut7 _lhsOppRE) <- return (inv_Expression_s8 sem arg7) | |
| 821;44 9: (T_Grammar_vOut10 _lhsOimp _lhsOpp) <- return (inv_Grammar_s11 sem arg10) | |
| 1043;28 9: (T_HsToken_vOut13 ) <- return (inv_HsToken_s14 sem arg13) | |
| 1139;29 9: (T_HsTokens_vOut16 ) <- return (inv_HsTokens_s17 sem arg16) | |
| 1194;33 9: (T_HsTokensRoot_vOut19 ) <- return (inv_HsTokensRoot_s20 sem arg19) | |
| 1237;182 9: (T_Nonterminal_vOut22 _lhsOextendedNTs _lhsOinhMap' _lhsOppA _lhsOppAI _lhsOppCata _lhsOppD _lhsOppDI _lhsOppL _lhsOppLI _lhsOppNtL _lhsOppR _lhsOppSF _lhsOppW _lhsOsynMap') <- return (inv_Nonterminal_s23 sem arg22) | |
| 1536;183 9: (T_Nonterminals_vOut25 _lhsOextendedNTs _lhsOinhMap' _lhsOppA _lhsOppAI _lhsOppCata _lhsOppD _lhsOppDI _lhsOppL _lhsOppLI _lhsOppNtL _lhsOppR _lhsOppSF _lhsOppW _lhsOsynMap') <- return (inv_Nonterminals_s26 sem arg25) | |
| 1811;47 9: (T_Pattern_vOut28 _lhsOcopy _lhsOinfo) <- return (inv_Pattern_s29 sem arg28) | |
| 1986;38 9: (T_Patterns_vOut31 _lhsOcopy) <- return (inv_Patterns_s32 sem arg31) | |
| 2059;159 9: (T_Production_vOut34 _lhsOhasMoreProds _lhsOppA _lhsOppCata _lhsOppD _lhsOppDI _lhsOppL _lhsOppLI _lhsOppR _lhsOppRA _lhsOppSF _lhsOppSPF _lhsOprdInh) <- return (inv_Production_s35 sem arg34) | |
| 2348;151 9: (T_Productions_vOut37 _lhsOhasMoreProds _lhsOppA _lhsOppCata _lhsOppDL _lhsOppL _lhsOppLI _lhsOppR _lhsOppRA _lhsOppSF _lhsOppSPF _lhsOprdInh) <- return (inv_Productions_s38 sem arg37) | |
| 2626;46 9: (T_Rule_vOut40 _lhsOlocals _lhsOppRL) <- return (inv_Rule_s41 sem arg40) | |
| 2699;47 9: (T_Rules_vOut43 _lhsOlocals _lhsOppRL) <- return (inv_Rules_s44 sem arg43) | |
| 2844;28 9: (T_TypeSig_vOut46 ) <- return (inv_TypeSig_s47 sem arg46) | |
| 2885;29 9: (T_TypeSigs_vOut49 ) <- return (inv_TypeSigs_s50 sem arg49) | |
| :uuagc-0.9.52.1/src-generated/CodeSyntaxDump.hs | |
| 70;35 9: (T_CGrammar_vOut1 _lhsOpp) <- return (inv_CGrammar_s2 sem arg1) | |
| 125;37 9: (T_CInterface_vOut4 _lhsOpp) <- return (inv_CInterface_s5 sem arg4) | |
| 176;39 9: (T_CNonterminal_vOut7 _lhsOpp) <- return (inv_CNonterminal_s8 sem arg7) | |
| 229;50 9: (T_CNonterminals_vOut10 _lhsOpp _lhsOppL) <- return (inv_CNonterminals_s11 sem arg10) | |
| 310;39 9: (T_CProduction_vOut13 _lhsOpp) <- return (inv_CProduction_s14 sem arg13) | |
| 361;49 9: (T_CProductions_vOut16 _lhsOpp _lhsOppL) <- return (inv_CProductions_s17 sem arg16) | |
| 442;33 9: (T_CRule_vOut19 _lhsOpp) <- return (inv_CRule_s20 sem arg19) | |
| 512;36 9: (T_CSegment_vOut22 _lhsOpp) <- return (inv_CSegment_s23 sem arg22) | |
| 561;46 9: (T_CSegments_vOut25 _lhsOpp _lhsOppL) <- return (inv_CSegments_s26 sem arg25) | |
| 642;34 9: (T_CVisit_vOut28 _lhsOpp) <- return (inv_CVisit_s29 sem arg28) | |
| 695;44 9: (T_CVisits_vOut31 _lhsOpp _lhsOppL) <- return (inv_CVisits_s32 sem arg31) | |
| 776;45 9: (T_Pattern_vOut34 _lhsOcopy _lhsOpp) <- return (inv_Pattern_s35 sem arg34) | |
| 951;55 9: (T_Patterns_vOut37 _lhsOcopy _lhsOpp _lhsOppL) <- return (inv_Patterns_s38 sem arg37) | |
| 1050;37 9: (T_Sequence_vOut40 _lhsOppL) <- return (inv_Sequence_s41 sem arg40) | |
| :uuagc-0.9.52.1/src-generated/DefaultRules.hs | |
| 472;102 9: !(T_Child_vOut0 _lhsOerrors _lhsOfield _lhsOinherited _lhsOname _lhsOoutput _lhsOsynthesized) <- return (inv_Child_s0 sem K_Child_v0 arg0) | |
| 681;89 9: !(T_Children_vOut1 _lhsOerrors _lhsOfields _lhsOinputs _lhsOoutput _lhsOoutputs) <- return (inv_Children_s2 sem K_Children_v1 arg1) | |
| 959;51 9: !(T_Grammar_vOut2 _lhsOerrors _lhsOoutput) <- return (inv_Grammar_s4 sem arg2) | |
| 1109;108 9: !(T_Nonterminal_vOut3 _lhsOcollect_nts _lhsOerrors _lhsOinhMap' _lhsOoutput _lhsOsynMap' _lhsOuniq) <- return (inv_Nonterminal_s6 sem K_Nonterminal_v3 arg3) | |
| 1557;109 9: !(T_Nonterminals_vOut4 _lhsOcollect_nts _lhsOerrors _lhsOinhMap' _lhsOoutput _lhsOsynMap' _lhsOuniq) <- return (inv_Nonterminals_s8 sem K_Nonterminals_v4 arg4) | |
| 2078;109 9: !(T_Pattern_vOut5 _lhsOcontainsVars _lhsOcopy _lhsOdefinedAttrs _lhsOerrors _lhsOlocals _lhsOoutput) <- return (inv_Pattern_s10 sem K_Pattern_v5 arg5) | |
| 2968;110 9: !(T_Patterns_vOut6 _lhsOcontainsVars _lhsOcopy _lhsOdefinedAttrs _lhsOerrors _lhsOlocals _lhsOoutput) <- return (inv_Patterns_s12 sem K_Patterns_v6 arg6) | |
| 3365;64 9: !(T_Production_vOut7 _lhsOerrors _lhsOoutput _lhsOuniq) <- return (inv_Production_s14 sem K_Production_v7 arg7) | |
| 3717;65 9: !(T_Productions_vOut8 _lhsOerrors _lhsOoutput _lhsOuniq) <- return (inv_Productions_s16 sem K_Productions_v8 arg8) | |
| 4135;146 9: !(T_Rule_vOut9 _lhsOcontainsVars _lhsOdefinedAttrs _lhsOerrors _lhsOisPure _lhsOlocals _lhsOoutput _lhsOoutputs _lhsOruleNames _lhsOuniq) <- return (inv_Rule_s18 sem K_Rule_v9 arg9) | |
| 4328;105 9: !(T_Rules_vOut10 _lhsOdefinedAttrs _lhsOerrors _lhsOlocals _lhsOoutput _lhsOruleNames _lhsOuniq) <- return (inv_Rules_s20 sem K_Rules_v10 arg10) | |
| 4593;40 9: !(T_TypeSig_vOut11 _lhsOoutput) <- return (inv_TypeSig_s22 sem arg11) | |
| 4649;41 9: !(T_TypeSigs_vOut12 _lhsOoutput) <- return (inv_TypeSigs_s24 sem arg12) | |
| :uuagc-0.9.52.1/src-generated/Desugar.hs | |
| 130;67 9: !(T_Child_vOut0 _lhsOchildInhs _lhsOchildSyns _lhsOoutput) <- return (inv_Child_s0 sem K_Child_v0 arg0) | |
| 242;70 9: !(T_Children_vOut1 _lhsOchildInhs _lhsOchildSyns _lhsOoutput) <- return (inv_Children_s2 sem K_Children_v1 arg1) | |
| 394;54 9: !(T_Expression_vOut2 _lhsOerrors _lhsOoutput) <- return (inv_Expression_s4 sem arg2) | |
| 460;70 9: !(T_Grammar_vOut3 _lhsOallAttributes _lhsOerrors _lhsOoutput) <- return (inv_Grammar_s6 sem arg3) | |
| 568;62 9: !(T_HsToken_vOut4 _lhsOaddLines _lhsOerrors _lhsOtks) <- return (inv_HsToken_s8 sem K_HsToken_v4 arg4) | |
| 1048;63 9: !(T_HsTokens_vOut5 _lhsOaddLines _lhsOerrors _lhsOtks) <- return (inv_HsTokens_s10 sem K_HsTokens_v5 arg5) | |
| 1310;53 9: !(T_HsTokensRoot_vOut6 _lhsOerrors _lhsOtks) <- return (inv_HsTokensRoot_s12 sem arg6) | |
| 1390;117 9: !(T_Nonterminal_vOut7 _lhsOallAttributes _lhsOaugmentsOut _lhsOerrors _lhsOinhMap' _lhsOoutput _lhsOsynMap') <- return (inv_Nonterminal_s14 sem K_Nonterminal_v7 arg7) | |
| 1575;118 9: !(T_Nonterminals_vOut8 _lhsOallAttributes _lhsOaugmentsOut _lhsOerrors _lhsOinhMap' _lhsOoutput _lhsOsynMap') <- return (inv_Nonterminals_s16 sem K_Nonterminals_v8 arg8) | |
| 1832;97 9: !(T_Pattern_vOut9 _lhsOallAttributes _lhsOcopy _lhsOdefsCollect _lhsOerrors _lhsOoutput) <- return (inv_Pattern_s18 sem K_Pattern_v9 arg9) | |
| 2883;99 9: !(T_Patterns_vOut10 _lhsOallAttributes _lhsOcopy _lhsOdefsCollect _lhsOerrors _lhsOoutput) <- return (inv_Patterns_s20 sem K_Patterns_v10 arg10) | |
| 3346;91 9: !(T_Production_vOut11 _lhsOallAttributes _lhsOaugmentsOut _lhsOerrors _lhsOoutput) <- return (inv_Production_s22 sem K_Production_v11 arg11) | |
| 3578;92 9: !(T_Productions_vOut12 _lhsOallAttributes _lhsOaugmentsOut _lhsOerrors _lhsOoutput) <- return (inv_Productions_s24 sem K_Productions_v12 arg12) | |
| 3856;85 9: !(T_Rule_vOut13 _lhsOallAttributes _lhsOdefsCollect _lhsOerrors _lhsOoutput) <- return (inv_Rule_s26 sem K_Rule_v13 arg13) | |
| 4062;86 9: !(T_Rules_vOut14 _lhsOallAttributes _lhsOdefsCollect _lhsOerrors _lhsOoutput) <- return (inv_Rules_s28 sem K_Rules_v14 arg14) | |
| 4357;40 9: !(T_TypeSig_vOut15 _lhsOoutput) <- return (inv_TypeSig_s30 sem arg15) | |
| 4407;41 9: !(T_TypeSigs_vOut16 _lhsOoutput) <- return (inv_TypeSigs_s32 sem arg16) | |
| :uuagc-0.9.52.1/src-generated/ExecutionPlan2Caml.hs | |
| 328;101 9: (T_EChild_vOut1 _lhsOargnamesw _lhsOchildTypes _lhsOchildintros _lhsOsigs _lhsOterminaldefs) <- return (inv_EChild_s2 sem arg1) | |
| 606;104 9: (T_EChildren_vOut4 _lhsOargnamesw _lhsOchildTypes _lhsOchildintros _lhsOsigs _lhsOterminaldefs) <- return (inv_EChildren_s5 sem arg4) | |
| 759;210 9: (T_ENonterminal_vOut7 _lhsOchildvisit _lhsOcode _lhsOdatas _lhsOerrors _lhsOfromToStates _lhsOinitStates _lhsOmodules _lhsOsemFunBndDefs _lhsOsemFunBndTps _lhsOvisitKinds _lhsOvisitdefs _lhsOvisituses) <- return (inv_ENonterminal_s8 sem arg7) | |
| 1475;212 9: (T_ENonterminals_vOut10 _lhsOchildvisit _lhsOcode _lhsOdatas _lhsOerrors _lhsOfromToStates _lhsOinitStates _lhsOmodules _lhsOsemFunBndDefs _lhsOsemFunBndTps _lhsOvisitKinds _lhsOvisitdefs _lhsOvisituses) <- return (inv_ENonterminals_s11 sem arg10) | |
| 1762;277 9: (T_EProduction_vOut13 _lhsOallvisits _lhsOchildvisit _lhsOcount _lhsOdatatype _lhsOdatatype_call _lhsOdatatype_con _lhsOerrors _lhsOfromToStates _lhsOsemFunBndDefs _lhsOsemFunBndTps _lhsOsem_nt _lhsOsem_prod _lhsOt_visits _lhsOvisitKinds _lhsOvisitdefs _lhsOvisituses) <- return (inv_EProduction_s14 sem arg13) | |
| 2343;278 9: (T_EProductions_vOut16 _lhsOallvisits _lhsOchildvisit _lhsOcount _lhsOdatatype _lhsOdatatype_call _lhsOdatatype_con _lhsOerrors _lhsOfromToStates _lhsOsemFunBndDefs _lhsOsemFunBndTps _lhsOsem_nt _lhsOsem_prod _lhsOt_visits _lhsOvisitKinds _lhsOvisitdefs _lhsOvisituses) <- return (inv_EProductions_s17 sem arg16) | |
| 2743;92 9: (T_ERule_vOut19 _lhsOerrors _lhsOmrules _lhsOruledefs _lhsOruleuses _lhsOsem_rules) <- return (inv_ERule_s20 sem arg19) | |
| 2975;93 9: (T_ERules_vOut22 _lhsOerrors _lhsOmrules _lhsOruledefs _lhsOruleuses _lhsOsem_rules) <- return (inv_ERules_s23 sem arg22) | |
| 3192;79 9: (T_ExecutionPlan_vOut25 _lhsOcode _lhsOdatas _lhsOerrors _lhsOmodules) <- return (inv_ExecutionPlan_s26 sem arg25) | |
| 3374;72 9: (T_Expression_vOut28 _lhsOattrs _lhsOpos _lhsOsemfunc _lhsOtks) <- return (inv_Expression_s29 sem arg28) | |
| 3454;47 9: (T_HsToken_vOut31 _lhsOattrs _lhsOtok) <- return (inv_HsToken_s32 sem arg31) | |
| 3659;37 9: (T_HsTokens_vOut34 _lhsOtks) <- return (inv_HsTokens_s35 sem arg34) | |
| 3738;33 9: (T_HsTokensRoot_vOut37 ) <- return (inv_HsTokensRoot_s38 sem arg37) | |
| 3785;109 9: (T_Pattern_vOut40 _lhsOattrTypes _lhsOattrs _lhsOcopy _lhsOextraDefs _lhsOisUnderscore _lhsOsem_lhs) <- return (inv_Pattern_s41 sem arg40) | |
| 4231;92 9: (T_Patterns_vOut43 _lhsOattrTypes _lhsOattrs _lhsOcopy _lhsOextraDefs _lhsOsem_lhs) <- return (inv_Patterns_s44 sem arg43) | |
| 4400;221 9: (T_Visit_vOut46 _lhsOallvisits _lhsOchildvisit _lhsOerrors _lhsOfromToStates _lhsOintramap _lhsOlazyIntras _lhsOruleKinds _lhsOruleUsage _lhsOsem_visit _lhsOt_visits _lhsOvisitKinds _lhsOvisitdefs _lhsOvisituses) <- return (inv_Visit_s47 sem arg46) | |
| 4852;181 9: (T_VisitStep_vOut49 _lhsOdefs _lhsOerrors _lhsOindex _lhsOisLast _lhsOlazyIntras _lhsOprevMaxSimRefs _lhsOruleKinds _lhsOruleUsage _lhsOsem_steps _lhsOuses _lhsOvisitKinds) <- return (inv_VisitStep_s50 sem arg49) | |
| 5442;192 9: (T_VisitSteps_vOut52 _lhsOdefs _lhsOerrors _lhsOindex _lhsOisLast _lhsOlazyIntras _lhsOprevMaxSimRefs _lhsOruleKinds _lhsOruleUsage _lhsOsem_steps _lhsOsize _lhsOuses _lhsOvisitKinds) <- return (inv_VisitSteps_s53 sem arg52) | |
| 5790;222 9: (T_Visits_vOut55 _lhsOallvisits _lhsOchildvisit _lhsOerrors _lhsOfromToStates _lhsOintramap _lhsOlazyIntras _lhsOruleKinds _lhsOruleUsage _lhsOsem_visit _lhsOt_visits _lhsOvisitKinds _lhsOvisitdefs _lhsOvisituses) <- return (inv_Visits_s56 sem arg55) | |
| :uuagc-0.9.52.1/src-generated/ExecutionPlan2Clean.hs | |
| 346;175 9: (T_EChild_vOut1 _lhsOargnamesw _lhsOargpats _lhsOargtps _lhsOchildTypes _lhsOchildintros _lhsOdatatype _lhsOrecfields _lhsOrecordtype _lhsOterminaldefs _lhsOusedArgs) <- return (inv_EChild_s2 sem arg1) | |
| 751;178 9: (T_EChildren_vOut4 _lhsOargnamesw _lhsOargpats _lhsOargtps _lhsOchildTypes _lhsOchildintros _lhsOdatatype _lhsOrecfields _lhsOrecordtype _lhsOterminaldefs _lhsOusedArgs) <- return (inv_EChildren_s5 sem arg4) | |
| 994;266 9: (T_ENonterminal_vOut7 _lhsOappendCommon _lhsOappendMain _lhsOchildvisit _lhsOerrors _lhsOfromToStates _lhsOgenProdIO _lhsOimports _lhsOinitStates _lhsOoutput _lhsOoutput_dcl _lhsOsemFunBndDefs _lhsOsemFunBndTps _lhsOvisitKinds _lhsOvisitdefs _lhsOvisituses) <- return (inv_ENonterminal_s8 sem arg7) | |
| 1842;268 9: (T_ENonterminals_vOut10 _lhsOappendCommon _lhsOappendMain _lhsOchildvisit _lhsOerrors _lhsOfromToStates _lhsOgenProdIO _lhsOimports _lhsOinitStates _lhsOoutput _lhsOoutput_dcl _lhsOsemFunBndDefs _lhsOsemFunBndTps _lhsOvisitKinds _lhsOvisitdefs _lhsOvisituses) <- return (inv_ENonterminals_s11 sem arg10) | |
| 2207;302 9: (T_EProduction_vOut13 _lhsOallvisits _lhsOchildvisit _lhsOcount _lhsOdatatype _lhsOerrors _lhsOfromToStates _lhsOgenProdIO _lhsOimports _lhsOrecordtype _lhsOsemFunBndDefs _lhsOsemFunBndTps _lhsOsem_nt _lhsOsem_prod _lhsOsem_prod_tys _lhsOt_visits _lhsOvisitKinds _lhsOvisitdefs _lhsOvisituses) <- return (inv_EProduction_s14 sem arg13) | |
| 2906;303 9: (T_EProductions_vOut16 _lhsOallvisits _lhsOchildvisit _lhsOcount _lhsOdatatype _lhsOerrors _lhsOfromToStates _lhsOgenProdIO _lhsOimports _lhsOrecordtype _lhsOsemFunBndDefs _lhsOsemFunBndTps _lhsOsem_nt _lhsOsem_prod _lhsOsem_prod_tys _lhsOt_visits _lhsOvisitKinds _lhsOvisitdefs _lhsOvisituses) <- return (inv_EProductions_s17 sem arg16) | |
| 3380;106 9: (T_ERule_vOut19 _lhsOerrors _lhsOmrules _lhsOruledefs _lhsOruleuses _lhsOsem_rules _lhsOusedArgs) <- return (inv_ERule_s20 sem arg19) | |
| 3646;107 9: (T_ERules_vOut22 _lhsOerrors _lhsOmrules _lhsOruledefs _lhsOruleuses _lhsOsem_rules _lhsOusedArgs) <- return (inv_ERules_s23 sem arg22) | |
| 3913;84 9: (T_ExecutionPlan_vOut25 _lhsOerrors _lhsOgenIO _lhsOoutput _lhsOoutput_dcl) <- return (inv_ExecutionPlan_s26 sem arg25) | |
| 4181;72 9: (T_Expression_vOut28 _lhsOattrs _lhsOpos _lhsOsemfunc _lhsOtks) <- return (inv_Expression_s29 sem arg28) | |
| 4261;47 9: (T_HsToken_vOut31 _lhsOattrs _lhsOtok) <- return (inv_HsToken_s32 sem arg31) | |
| 4466;37 9: (T_HsTokens_vOut34 _lhsOtks) <- return (inv_HsTokens_s35 sem arg34) | |
| 4545;33 9: (T_HsTokensRoot_vOut37 ) <- return (inv_HsTokensRoot_s38 sem arg37) | |
| 4592;94 9: (T_Pattern_vOut40 _lhsOattrTypes _lhsOattrs _lhsOcopy _lhsOisUnderscore _lhsOsem_lhs) <- return (inv_Pattern_s41 sem arg40) | |
| 5044;77 9: (T_Patterns_vOut43 _lhsOattrTypes _lhsOattrs _lhsOcopy _lhsOsem_lhs) <- return (inv_Patterns_s44 sem arg43) | |
| 5203;235 9: (T_Visit_vOut46 _lhsOallvisits _lhsOchildvisit _lhsOerrors _lhsOfromToStates _lhsOintramap _lhsOlazyIntras _lhsOruleKinds _lhsOruleUsage _lhsOsem_visit _lhsOt_visits _lhsOusedArgs _lhsOvisitKinds _lhsOvisitdefs _lhsOvisituses) <- return (inv_Visit_s47 sem arg46) | |
| 5711;175 9: (T_VisitStep_vOut49 _lhsOdefs _lhsOerrors _lhsOindex _lhsOisLast _lhsOlazyIntras _lhsOruleKinds _lhsOruleUsage _lhsOsem_steps _lhsOusedArgs _lhsOuses _lhsOvisitKinds) <- return (inv_VisitStep_s50 sem arg49) | |
| 6311;186 9: (T_VisitSteps_vOut52 _lhsOdefs _lhsOerrors _lhsOindex _lhsOisLast _lhsOlazyIntras _lhsOruleKinds _lhsOruleUsage _lhsOsem_steps _lhsOsize _lhsOusedArgs _lhsOuses _lhsOvisitKinds) <- return (inv_VisitSteps_s53 sem arg52) | |
| 6634;236 9: (T_Visits_vOut55 _lhsOallvisits _lhsOchildvisit _lhsOerrors _lhsOfromToStates _lhsOintramap _lhsOlazyIntras _lhsOruleKinds _lhsOruleUsage _lhsOsem_visit _lhsOt_visits _lhsOusedArgs _lhsOvisitKinds _lhsOvisitdefs _lhsOvisituses) <- return (inv_Visits_s56 sem arg55) | |
| :uuagc-0.9.52.1/src-generated/ExecutionPlan2Hs.hs | |
| 339;144 9: (T_EChild_vOut1 _lhsOargnamesw _lhsOargpats _lhsOargtps _lhsOchildTypes _lhsOchildintros _lhsOdatatype _lhsOterminaldefs _lhsOusedArgs) <- return (inv_EChild_s2 sem arg1) | |
| 693;147 9: (T_EChildren_vOut4 _lhsOargnamesw _lhsOargpats _lhsOargtps _lhsOchildTypes _lhsOchildintros _lhsOdatatype _lhsOterminaldefs _lhsOusedArgs) <- return (inv_EChildren_s5 sem arg4) | |
| 908;250 9: (T_ENonterminal_vOut7 _lhsOappendCommon _lhsOappendMain _lhsOchildvisit _lhsOerrors _lhsOfromToStates _lhsOgenProdIO _lhsOimports _lhsOinitStates _lhsOoutput _lhsOsemFunBndDefs _lhsOsemFunBndTps _lhsOvisitKinds _lhsOvisitdefs _lhsOvisituses) <- return (inv_ENonterminal_s8 sem arg7) | |
| 1693;252 9: (T_ENonterminals_vOut10 _lhsOappendCommon _lhsOappendMain _lhsOchildvisit _lhsOerrors _lhsOfromToStates _lhsOgenProdIO _lhsOimports _lhsOinitStates _lhsOoutput _lhsOsemFunBndDefs _lhsOsemFunBndTps _lhsOvisitKinds _lhsOvisitdefs _lhsOvisituses) <- return (inv_ENonterminals_s11 sem arg10) | |
| 2040;268 9: (T_EProduction_vOut13 _lhsOallvisits _lhsOchildvisit _lhsOcount _lhsOdatatype _lhsOerrors _lhsOfromToStates _lhsOgenProdIO _lhsOimports _lhsOsemFunBndDefs _lhsOsemFunBndTps _lhsOsem_nt _lhsOsem_prod _lhsOt_visits _lhsOvisitKinds _lhsOvisitdefs _lhsOvisituses) <- return (inv_EProduction_s14 sem arg13) | |
| 2754;269 9: (T_EProductions_vOut16 _lhsOallvisits _lhsOchildvisit _lhsOcount _lhsOdatatype _lhsOerrors _lhsOfromToStates _lhsOgenProdIO _lhsOimports _lhsOsemFunBndDefs _lhsOsemFunBndTps _lhsOsem_nt _lhsOsem_prod _lhsOt_visits _lhsOvisitKinds _lhsOvisitdefs _lhsOvisituses) <- return (inv_EProductions_s17 sem arg16) | |
| 3194;106 9: (T_ERule_vOut19 _lhsOerrors _lhsOmrules _lhsOruledefs _lhsOruleuses _lhsOsem_rules _lhsOusedArgs) <- return (inv_ERule_s20 sem arg19) | |
| 3497;107 9: (T_ERules_vOut22 _lhsOerrors _lhsOmrules _lhsOruledefs _lhsOruleuses _lhsOsem_rules _lhsOusedArgs) <- return (inv_ERules_s23 sem arg22) | |
| 3756;68 9: (T_ExecutionPlan_vOut25 _lhsOerrors _lhsOgenIO _lhsOoutput) <- return (inv_ExecutionPlan_s26 sem arg25) | |
| 4030;72 9: (T_Expression_vOut28 _lhsOattrs _lhsOpos _lhsOsemfunc _lhsOtks) <- return (inv_Expression_s29 sem arg28) | |
| 4110;47 9: (T_HsToken_vOut31 _lhsOattrs _lhsOtok) <- return (inv_HsToken_s32 sem arg31) | |
| 4315;37 9: (T_HsTokens_vOut34 _lhsOtks) <- return (inv_HsTokens_s35 sem arg34) | |
| 4394;33 9: (T_HsTokensRoot_vOut37 ) <- return (inv_HsTokensRoot_s38 sem arg37) | |
| 4441;94 9: (T_Pattern_vOut40 _lhsOattrTypes _lhsOattrs _lhsOcopy _lhsOisUnderscore _lhsOsem_lhs) <- return (inv_Pattern_s41 sem arg40) | |
| 4894;77 9: (T_Patterns_vOut43 _lhsOattrTypes _lhsOattrs _lhsOcopy _lhsOsem_lhs) <- return (inv_Patterns_s44 sem arg43) | |
| 5053;235 9: (T_Visit_vOut46 _lhsOallvisits _lhsOchildvisit _lhsOerrors _lhsOfromToStates _lhsOintramap _lhsOlazyIntras _lhsOruleKinds _lhsOruleUsage _lhsOsem_visit _lhsOt_visits _lhsOusedArgs _lhsOvisitKinds _lhsOvisitdefs _lhsOvisituses) <- return (inv_Visit_s47 sem arg46) | |
| 5588;211 9: (T_VisitStep_vOut49 _lhsOdefs _lhsOerrors _lhsOindex _lhsOisLast _lhsOlazyIntras _lhsOprevMaxSimRefs _lhsOruleKinds _lhsOruleUsage _lhsOsem_steps _lhsOsync_steps _lhsOusedArgs _lhsOuses _lhsOvisitKinds) <- return (inv_VisitStep_s50 sem arg49) | |
| 6281;222 9: (T_VisitSteps_vOut52 _lhsOdefs _lhsOerrors _lhsOindex _lhsOisLast _lhsOlazyIntras _lhsOprevMaxSimRefs _lhsOruleKinds _lhsOruleUsage _lhsOsem_steps _lhsOsize _lhsOsync_steps _lhsOusedArgs _lhsOuses _lhsOvisitKinds) <- return (inv_VisitSteps_s53 sem arg52) | |
| 6640;236 9: (T_Visits_vOut55 _lhsOallvisits _lhsOchildvisit _lhsOerrors _lhsOfromToStates _lhsOintramap _lhsOlazyIntras _lhsOruleKinds _lhsOruleUsage _lhsOsem_visit _lhsOt_visits _lhsOusedArgs _lhsOvisitKinds _lhsOvisitdefs _lhsOvisituses) <- return (inv_Visits_s56 sem arg55) | |
| :uuagc-0.9.52.1/src-generated/GenerateCode.hs | |
| 276;51 9: (T_CGrammar_vOut1 _lhsOerrors _lhsOoutput) <- return (inv_CGrammar_s2 sem arg1) | |
| 565;92 9: (T_CInterface_vOut4 _lhsOcomments _lhsOsemDom _lhsOsemDomUnfoldGath _lhsOwrapDecls) <- return (inv_CInterface_s5 sem arg4) | |
| 726;78 9: (T_CNonterminal_vOut7 _lhsOchunks _lhsOgathNts _lhsOsemDomUnfoldGath) <- return (inv_CNonterminal_s8 sem arg7) | |
| 1187;80 9: (T_CNonterminals_vOut10 _lhsOchunks _lhsOgathNts _lhsOsemDomUnfoldGath) <- return (inv_CNonterminals_s11 sem arg10) | |
| 1512;96 9: (T_CProduction_vOut13 _lhsOcataAlt _lhsOcomments _lhsOdataAlt _lhsOdecls _lhsOsemNames) <- return (inv_CProduction_s14 sem arg13) | |
| 1810;99 9: (T_CProductions_vOut16 _lhsOcataAlts _lhsOcomments _lhsOdataAlts _lhsOdecls _lhsOsemNames) <- return (inv_CProductions_s17 sem arg16) | |
| 2175;180 9: (T_CRule_vOut19 _lhsOallTpsFound _lhsObldBlocksFun _lhsOcomments _lhsOdecls _lhsOdeclsAbove _lhsOdefinedInsts _lhsOexprs _lhsOtSigs _lhsOtps _lhsOusedVars _lhsOvisitedSet) <- return (inv_CRule_s20 sem arg19) | |
| 2682;91 9: (T_CSegment_vOut22 _lhsOcomments _lhsOsemDom _lhsOsemDomUnfoldGath _lhsOwrapDecls) <- return (inv_CSegment_s23 sem arg22) | |
| 2884;103 9: (T_CSegments_vOut25 _lhsOcomments _lhsOisNil _lhsOsemDom _lhsOsemDomUnfoldGath _lhsOwrapDecls) <- return (inv_CSegments_s26 sem arg25) | |
| 3189;131 9: (T_CVisit_vOut28 _lhsOcomments _lhsOdecls _lhsOgatherInstVisitNrs _lhsOintra _lhsOintraVars _lhsOsemNames _lhsOvisitedSet) <- return (inv_CVisit_s29 sem arg28) | |
| 3813;143 9: (T_CVisits_vOut31 _lhsOcomments _lhsOdecls _lhsOgatherInstVisitNrs _lhsOintra _lhsOintraVars _lhsOisNil _lhsOsemNames _lhsOvisitedSet) <- return (inv_CVisits_s32 sem arg31) | |
| 4307;69 9: (T_DeclBlocks_vOut34 _lhsOcallExpr _lhsOdecls _lhsOfreeVars) <- return (inv_DeclBlocks_s35 sem arg34) | |
| 4475;62 9: (T_DeclBlocksRoot_vOut37 _lhsOfirstCall _lhsOlambdas) <- return (inv_DeclBlocksRoot_s38 sem arg37) | |
| 4557;78 9: (T_Pattern_vOut40 _lhsOcopy _lhsOdefinedInsts _lhsOpatternAttributes) <- return (inv_Pattern_s41 sem arg40) | |
| 4751;79 9: (T_Patterns_vOut43 _lhsOcopy _lhsOdefinedInsts _lhsOpatternAttributes) <- return (inv_Patterns_s44 sem arg43) | |
| 4844;181 9: (T_Sequence_vOut46 _lhsOallTpsFound _lhsOblockDecls _lhsOcomments _lhsOdecls _lhsOdeclsAbove _lhsOdefinedInsts _lhsOexprs _lhsOtSigs _lhsOtps _lhsOusedVars _lhsOvisitedSet) <- return (inv_Sequence_s47 sem arg46) | |
| :uuagc-0.9.52.1/src-generated/InterfacesRules.hs | |
| 103;58 9: !(T_IRoot_vOut1 _lhsOedp _lhsOinters _lhsOvisits) <- return (inv_IRoot_s2 sem arg1) | |
| 234;125 9: !(T_Interface_vOut4 _lhsOdescr _lhsOedp _lhsOfirstvisitvertices _lhsOinter _lhsOnewedges _lhsOnt _lhsOv _lhsOvisits) <- return (inv_Interface_s5 sem arg4) | |
| 430;119 9: !(T_Interfaces_vOut7 _lhsOdescr _lhsOedp _lhsOfirstvisitvertices _lhsOinters _lhsOnewedges _lhsOv _lhsOvisits) <- return (inv_Interfaces_s8 sem arg7) | |
| 623;169 9: !(T_Segment_vOut10 _lhsOcvisits _lhsOdescr _lhsOedp _lhsOgroups _lhsOinh _lhsOintravisits _lhsOnewedges _lhsOnewvertices _lhsOprev _lhsOseg _lhsOv _lhsOvisitss) <- return (inv_Segment_s11 sem arg10) | |
| 909;165 9: !(T_Segments_vOut13 _lhsOcvisits _lhsOdescr _lhsOedp _lhsOfirstInh _lhsOgroups _lhsOhdIntravisits _lhsOnewedges _lhsOnewvertices _lhsOprev _lhsOsegs _lhsOv) <- return (inv_Segments_s14 sem arg13) | |
| :uuagc-0.9.52.1/src-generated/KWOrder.hs | |
| 88;103 9: (T_Child_vOut1 _lhsOechilds _lhsOedges _lhsOnontnames _lhsOrefHoNts _lhsOrefNts _lhsOvertices) <- return (inv_Child_s2 sem arg1) | |
| 312;106 9: (T_Children_vOut4 _lhsOechilds _lhsOedges _lhsOnontnames _lhsOrefHoNts _lhsOrefNts _lhsOvertices) <- return (inv_Children_s5 sem arg4) | |
| 475;53 9: (T_Expression_vOut7 _lhsOcopy _lhsOvertices) <- return (inv_Expression_s8 sem arg7) | |
| 534;123 9: (T_Grammar_vOut10 _lhsOdepgraphs _lhsOerrors _lhsOinhmap _lhsOlocalSigMap _lhsOoutput _lhsOsynmap _lhsOvisitgraph) <- return (inv_Grammar_s11 sem arg10) | |
| 694;41 9: (T_HsToken_vOut13 _lhsOvertices) <- return (inv_HsToken_s14 sem arg13) | |
| 828;29 9: (T_HsTokens_vOut16 ) <- return (inv_HsTokens_s17 sem arg16) | |
| 883;33 9: (T_HsTokensRoot_vOut19 ) <- return (inv_HsTokensRoot_s20 sem arg19) | |
| 926;153 9: (T_Nonterminal_vOut22 _lhsOdepinfo _lhsOinhMap' _lhsOinhmap _lhsOlocalSigMap _lhsOntDeps _lhsOntHoDeps _lhsOrulenumber _lhsOsynMap' _lhsOsynmap) <- return (inv_Nonterminal_s23 sem arg22) | |
| 1173;154 9: (T_Nonterminals_vOut25 _lhsOdepinfo _lhsOinhMap' _lhsOinhmap _lhsOlocalSigMap _lhsOntDeps _lhsOntHoDeps _lhsOrulenumber _lhsOsynMap' _lhsOsynmap) <- return (inv_Nonterminals_s26 sem arg25) | |
| 1406;51 9: (T_Pattern_vOut28 _lhsOcopy _lhsOvertices) <- return (inv_Pattern_s29 sem arg28) | |
| 1582;52 9: (T_Patterns_vOut31 _lhsOcopy _lhsOvertices) <- return (inv_Patterns_s32 sem arg31) | |
| 1665;103 9: (T_Production_vOut34 _lhsOdepgraph _lhsOlocalSigMap _lhsOrefHoNts _lhsOrefNts _lhsOrulenumber) <- return (inv_Production_s35 sem arg34) | |
| 1827;104 9: (T_Productions_vOut37 _lhsOdepgraph _lhsOlocalSigMap _lhsOrefHoNts _lhsOrefNts _lhsOrulenumber) <- return (inv_Productions_s38 sem arg37) | |
| 1988;77 9: (T_Rule_vOut40 _lhsOedges _lhsOerules _lhsOrulenumber _lhsOvertices) <- return (inv_Rule_s41 sem arg40) | |
| 2100;78 9: (T_Rules_vOut43 _lhsOedges _lhsOerules _lhsOrulenumber _lhsOvertices) <- return (inv_Rules_s44 sem arg43) | |
| 2203;44 9: (T_TypeSig_vOut46 _lhsOlocalSigMap) <- return (inv_TypeSig_s47 sem arg46) | |
| 2252;45 9: (T_TypeSigs_vOut49 _lhsOlocalSigMap) <- return (inv_TypeSigs_s50 sem arg49) | |
| :uuagc-0.9.52.1/src-generated/LOAG/Order.hs | |
| 340;37 9: (T_CGrammar_vOut1 _lhsOself) <- return (inv_CGrammar_s2 sem arg1) | |
| 392;39 9: (T_CInterface_vOut4 _lhsOself) <- return (inv_CInterface_s5 sem arg4) | |
| 444;41 9: (T_CNonterminal_vOut7 _lhsOself) <- return (inv_CNonterminal_s8 sem arg7) | |
| 498;43 9: (T_CNonterminals_vOut10 _lhsOself) <- return (inv_CNonterminals_s11 sem arg10) | |
| 571;41 9: (T_CProduction_vOut13 _lhsOself) <- return (inv_CProduction_s14 sem arg13) | |
| 623;42 9: (T_CProductions_vOut16 _lhsOself) <- return (inv_CProductions_s17 sem arg16) | |
| 696;35 9: (T_CRule_vOut19 _lhsOself) <- return (inv_CRule_s20 sem arg19) | |
| 768;38 9: (T_CSegment_vOut22 _lhsOself) <- return (inv_CSegment_s23 sem arg22) | |
| 818;39 9: (T_CSegments_vOut25 _lhsOself) <- return (inv_CSegments_s26 sem arg25) | |
| 891;36 9: (T_CVisit_vOut28 _lhsOself) <- return (inv_CVisit_s29 sem arg28) | |
| 945;37 9: (T_CVisits_vOut31 _lhsOself) <- return (inv_CVisits_s32 sem arg31) | |
| 1018;193 9: (T_Child_vOut34 _lhsOap _lhsOechilds _lhsOfieldMap _lhsOflab _lhsOfty _lhsOgen _lhsOhoMap _lhsOinss _lhsOofld _lhsOolab _lhsOpmp _lhsOpmpr _lhsOpts _lhsOrefHoNts _lhsOrefNts _lhsOself) <- return (inv_Child_s35 sem arg34) | |
| 1291;196 9: (T_Children_vOut37 _lhsOap _lhsOechilds _lhsOfieldMap _lhsOflab _lhsOfty _lhsOgen _lhsOhoMap _lhsOinss _lhsOofld _lhsOolab _lhsOpmp _lhsOpmpr _lhsOpts _lhsOrefHoNts _lhsOrefNts _lhsOself) <- return (inv_Children_s38 sem arg37) | |
| 1728;60 9: (T_Expression_vOut40 _lhsOcopy _lhsOself _lhsOused) <- return (inv_Expression_s41 sem arg40) | |
| 1818;123 9: (T_FieldAtt_vOut43 _lhsOap _lhsOflab _lhsOfty _lhsOgen _lhsOinss _lhsOofld _lhsOolab _lhsOpmp _lhsOpmpr _lhsOself) <- return (inv_FieldAtt_s44 sem arg43) | |
| 1975;124 9: (T_FieldAtts_vOut46 _lhsOap _lhsOflab _lhsOfty _lhsOgen _lhsOinss _lhsOofld _lhsOolab _lhsOpmp _lhsOpmpr _lhsOself) <- return (inv_FieldAtts_s47 sem arg46) | |
| 2170;111 9: (T_Grammar_vOut49 _lhsOads _lhsOerrors _lhsOinhmap _lhsOlocalSigMap _lhsOoutput _lhsOself _lhsOsynmap) <- return (inv_Grammar_s50 sem arg49) | |
| 2571;47 9: (T_HsToken_vOut52 _lhsOself _lhsOused) <- return (inv_HsToken_s53 sem arg52) | |
| 2761;48 9: (T_HsTokens_vOut55 _lhsOself _lhsOused) <- return (inv_HsTokens_s56 sem arg55) | |
| 2860;52 9: (T_HsTokensRoot_vOut58 _lhsOself _lhsOused) <- return (inv_HsTokensRoot_s59 sem arg58) | |
| 2925;37 9: (T_LOAGRep_vOut61 _lhsOself) <- return (inv_LOAGRep_s62 sem arg61) | |
| 2977;98 9: (T_MySegment_vOut64 _lhsOdone _lhsOevisits _lhsOself _lhsOsynsO _lhsOvisitnum _lhsOvisnr) <- return (inv_MySegment_s65 sem arg64) | |
| 3120;67 9: (T_MySegments_vOut67 _lhsOevisits _lhsOself _lhsOvisitnum) <- return (inv_MySegments_s68 sem arg67) | |
| 3350;371 9: (T_Nonterminal_vOut70 _lhsOads _lhsOap _lhsOenonts _lhsOfdps _lhsOfieldMap _lhsOflab _lhsOfsInP _lhsOfty _lhsOgen _lhsOhoMap _lhsOinhmap _lhsOinhs _lhsOinss _lhsOlfp _lhsOlfpr _lhsOlocalSigMap _lhsOntDeps _lhsOntHoDeps _lhsOofld _lhsOolab _lhsOpmp _lhsOpmpr _lhsOps _lhsOruleMap _lhsOrulenumber _lhsOself _lhsOsfp _lhsOsynmap _lhsOsyns _lhsOvisMap _lhsOvisitnum) <- return (inv_Nonterminal_s71 sem arg70) | |
| 3850;372 9: (T_Nonterminals_vOut73 _lhsOads _lhsOap _lhsOenonts _lhsOfdps _lhsOfieldMap _lhsOflab _lhsOfsInP _lhsOfty _lhsOgen _lhsOhoMap _lhsOinhmap _lhsOinhs _lhsOinss _lhsOlfp _lhsOlfpr _lhsOlocalSigMap _lhsOntDeps _lhsOntHoDeps _lhsOofld _lhsOolab _lhsOpmp _lhsOpmpr _lhsOps _lhsOruleMap _lhsOrulenumber _lhsOself _lhsOsfp _lhsOsynmap _lhsOsyns _lhsOvisMap _lhsOvisitnum) <- return (inv_Nonterminals_s74 sem arg73) | |
| 4439;56 9: (T_Pattern_vOut76 _lhsOafs _lhsOcopy _lhsOself) <- return (inv_Pattern_s77 sem arg76) | |
| 4652;57 9: (T_Patterns_vOut79 _lhsOafs _lhsOcopy _lhsOself) <- return (inv_Patterns_s80 sem arg79) | |
| 4753;314 9: (T_Production_vOut82 _lhsOads _lhsOap _lhsOeprods _lhsOfdps _lhsOfieldMap _lhsOflab _lhsOfsInP _lhsOfty _lhsOgen _lhsOhoMap _lhsOinss _lhsOlfp _lhsOlfpr _lhsOlocalSigMap _lhsOofld _lhsOolab _lhsOpmp _lhsOpmpr _lhsOps _lhsOrefHoNts _lhsOrefNts _lhsOruleMap _lhsOrulenumber _lhsOself _lhsOsfp _lhsOvisitnum) <- return (inv_Production_s83 sem arg82) | |
| 5200;315 9: (T_Productions_vOut85 _lhsOads _lhsOap _lhsOeprods _lhsOfdps _lhsOfieldMap _lhsOflab _lhsOfsInP _lhsOfty _lhsOgen _lhsOhoMap _lhsOinss _lhsOlfp _lhsOlfpr _lhsOlocalSigMap _lhsOofld _lhsOolab _lhsOpmp _lhsOpmpr _lhsOps _lhsOrefHoNts _lhsOrefNts _lhsOruleMap _lhsOrulenumber _lhsOself _lhsOsfp _lhsOvisitnum) <- return (inv_Productions_s86 sem arg85) | |
| 5721;129 9: (T_Rule_vOut88 _lhsOerules _lhsOlfp _lhsOlfpr _lhsOruleMap _lhsOrulenumber _lhsOself _lhsOsfp _lhsOused _lhsOusedLocals) <- return (inv_Rule_s89 sem arg88) | |
| 5866;120 9: (T_Rules_vOut91 _lhsOerules _lhsOlfp _lhsOlfpr _lhsOruleMap _lhsOrulenumber _lhsOself _lhsOsfp _lhsOusedLocals) <- return (inv_Rules_s92 sem arg91) | |
| 6049;38 9: (T_Sequence_vOut94 _lhsOself) <- return (inv_Sequence_s95 sem arg94) | |
| 6122;54 9: (T_TypeSig_vOut97 _lhsOlocalSigMap _lhsOself) <- return (inv_TypeSig_s98 sem arg97) | |
| 6180;56 9: (T_TypeSigs_vOut100 _lhsOlocalSigMap _lhsOself) <- return (inv_TypeSigs_s101 sem arg100) | |
| :uuagc-0.9.52.1/src-generated/Order.hs | |
| 239;198 9: (T_Child_vOut1 _lhsOattributes _lhsOcollectChildrenInhs _lhsOcollectChildrenSyns _lhsOerrors _lhsOfield _lhsOgathAltAttrs _lhsOgathRules _lhsOinhs _lhsOnts _lhsOsinglevisits _lhsOterminals) <- return (inv_Child_s2 sem arg1) | |
| 410;202 9: (T_Children_vOut4 _lhsOattributes _lhsOcollectChildrenInhs _lhsOcollectChildrenSyns _lhsOerrors _lhsOfields _lhsOgathAltAttrs _lhsOgathRules _lhsOinhs _lhsOnts _lhsOsinglevisits _lhsOterminals) <- return (inv_Children_s5 sem arg4) | |
| 669;129 9: (T_Expression_vOut7 _lhsOallRhsVars _lhsOcopy _lhsOerrors _lhsOtextLines _lhsOusedAttrs _lhsOusedFields _lhsOusedLocals) <- return (inv_Expression_s8 sem arg7) | |
| 787;87 9: (T_Grammar_vOut10 _lhsOerrors _lhsOnAutoRules _lhsOnExplicitRules _lhsOoutput) <- return (inv_Grammar_s11 sem arg10) | |
| 1127;271 9: (T_Nonterminal_vOut13 _lhsOacount _lhsOadditionalDep _lhsOaranges _lhsOaroundDep _lhsOcNonterminal _lhsOdirectDep _lhsOerrors _lhsOinhMap' _lhsOinstDep _lhsOmergeDep _lhsOnAutoRules _lhsOnExplicitRules _lhsOnonts _lhsOntattrs _lhsOrules _lhsOsynMap' _lhsOvcount) <- return (inv_Nonterminal_s14 sem arg13) | |
| 1407;273 9: (T_Nonterminals_vOut16 _lhsOacount _lhsOadditionalDep _lhsOaranges _lhsOaroundDep _lhsOcNonterminals _lhsOdirectDep _lhsOerrors _lhsOinhMap' _lhsOinstDep _lhsOmergeDep _lhsOnAutoRules _lhsOnExplicitRules _lhsOnonts _lhsOntattrs _lhsOrules _lhsOsynMap' _lhsOvcount) <- return (inv_Nonterminals_s17 sem arg16) | |
| 1814;112 9: (T_Pattern_vOut19 _lhsOcopy _lhsOerrors _lhsOgathAltAttrs _lhsOinstVars _lhsOlocVars _lhsOpatternAttrs) <- return (inv_Pattern_s20 sem arg19) | |
| 2189;113 9: (T_Patterns_vOut22 _lhsOcopy _lhsOerrors _lhsOgathAltAttrs _lhsOinstVars _lhsOlocVars _lhsOpatternAttrs) <- return (inv_Patterns_s23 sem arg22) | |
| 2360;204 9: (T_Production_vOut25 _lhsOadditionalDep _lhsOaroundDep _lhsOcProduction _lhsOcons _lhsOdirectDep _lhsOerrors _lhsOinstDep _lhsOmergeDep _lhsOnAutoRules _lhsOnExplicitRules _lhsOrules _lhsOvcount) <- return (inv_Production_s26 sem arg25) | |
| 2821;206 9: (T_Productions_vOut28 _lhsOadditionalDep _lhsOaroundDep _lhsOcProductions _lhsOcons _lhsOdirectDep _lhsOerrors _lhsOinstDep _lhsOmergeDep _lhsOnAutoRules _lhsOnExplicitRules _lhsOrules _lhsOvcount) <- return (inv_Productions_s29 sem arg28) | |
| 3178;160 9: (T_Rule_vOut31 _lhsOdirectDep _lhsOerrors _lhsOgathAltAttrs _lhsOgathRules _lhsOinstDep _lhsOinstVars _lhsOlocVars _lhsOnAutoRules _lhsOnExplicitRules) <- return (inv_Rule_s32 sem arg31) | |
| 3399;161 9: (T_Rules_vOut34 _lhsOdirectDep _lhsOerrors _lhsOgathAltAttrs _lhsOgathRules _lhsOinstDep _lhsOinstVars _lhsOlocVars _lhsOnAutoRules _lhsOnExplicitRules) <- return (inv_Rules_s35 sem arg34) | |
| 3736;41 9: (T_TypeSig_vOut37 _lhsOtypeSigs) <- return (inv_TypeSig_s38 sem arg37) | |
| 3785;42 9: (T_TypeSigs_vOut40 _lhsOtypeSigs) <- return (inv_TypeSigs_s41 sem arg40) | |
| :uuagc-0.9.52.1/src-generated/PrintCleanCode.hs | |
| 129;36 9: !(T_CaseAlt_vOut1 _lhsOpps) <- return (inv_CaseAlt_s2 sem arg1) | |
| 213;37 9: !(T_CaseAlts_vOut4 _lhsOpps) <- return (inv_CaseAlts_s5 sem arg4) | |
| 308;94 9: !(T_Chunk_vOut7 _lhsOappendCommon _lhsOappendMain _lhsOgenSems _lhsOimports _lhsOpps) <- return (inv_Chunk_s8 sem arg7) | |
| 556;96 9: !(T_Chunks_vOut10 _lhsOappendCommon _lhsOappendMain _lhsOgenSems _lhsOimports _lhsOpps) <- return (inv_Chunks_s11 sem arg10) | |
| 755;45 9: !(T_DataAlt_vOut13 _lhsOpp _lhsOppa) <- return (inv_DataAlt_s14 sem arg13) | |
| 854;48 9: !(T_DataAlts_vOut16 _lhsOppas _lhsOpps) <- return (inv_DataAlts_s17 sem arg16) | |
| 957;42 9: !(T_Decl_vOut19 _lhsOpp _lhsOppa) <- return (inv_Decl_s20 sem arg19) | |
| 1470;35 9: !(T_Decls_vOut22 _lhsOpps) <- return (inv_Decls_s23 sem arg22) | |
| 1573;33 9: !(T_Expr_vOut25 _lhsOpp) <- return (inv_Expr_s26 sem arg25) | |
| 2358;35 9: !(T_Exprs_vOut28 _lhsOpps) <- return (inv_Exprs_s29 sem arg28) | |
| 2453;32 9: !(T_Lhs_vOut31 _lhsOpp) <- return (inv_Lhs_s32 sem arg31) | |
| 2778;47 9: !(T_NamedType_vOut34 _lhsOpp _lhsOppa) <- return (inv_NamedType_s35 sem arg34) | |
| 2843;50 9: !(T_NamedTypes_vOut37 _lhsOppas _lhsOpps) <- return (inv_NamedTypes_s38 sem arg37) | |
| 2938;89 9: !(T_Pattern_vOut40 _lhsOcopy _lhsOisUnderscore _lhsOpp _lhsOpp' _lhsOstrictVars) <- return (inv_Pattern_s41 sem arg40) | |
| 3338;74 9: !(T_Patterns_vOut43 _lhsOcopy _lhsOpps _lhsOpps' _lhsOstrictVars) <- return (inv_Patterns_s44 sem arg43) | |
| 3477;51 9: !(T_Program_vOut46 _lhsOgenIO _lhsOoutput) <- return (inv_Program_s47 sem arg46) | |
| 3640;53 9: !(T_Type_vOut49 _lhsOcopy _lhsOpp _lhsOprec) <- return (inv_Type_s50 sem arg49) | |
| 4322;45 9: !(T_Types_vOut52 _lhsOcopy _lhsOpps) <- return (inv_Types_s53 sem arg52) | |
| :uuagc-0.9.52.1/src-generated/PrintCode.hs | |
| 127;36 9: !(T_CaseAlt_vOut1 _lhsOpps) <- return (inv_CaseAlt_s2 sem arg1) | |
| 211;37 9: !(T_CaseAlts_vOut4 _lhsOpps) <- return (inv_CaseAlts_s5 sem arg4) | |
| 306;94 9: !(T_Chunk_vOut7 _lhsOappendCommon _lhsOappendMain _lhsOgenSems _lhsOimports _lhsOpps) <- return (inv_Chunk_s8 sem arg7) | |
| 554;96 9: !(T_Chunks_vOut10 _lhsOappendCommon _lhsOappendMain _lhsOgenSems _lhsOimports _lhsOpps) <- return (inv_Chunks_s11 sem arg10) | |
| 753;36 9: !(T_DataAlt_vOut13 _lhsOpp) <- return (inv_DataAlt_s14 sem arg13) | |
| 833;38 9: !(T_DataAlts_vOut16 _lhsOpps) <- return (inv_DataAlts_s17 sem arg16) | |
| 920;33 9: !(T_Decl_vOut19 _lhsOpp) <- return (inv_Decl_s20 sem arg19) | |
| 1377;35 9: !(T_Decls_vOut22 _lhsOpps) <- return (inv_Decls_s23 sem arg22) | |
| 1480;33 9: !(T_Expr_vOut25 _lhsOpp) <- return (inv_Expr_s26 sem arg25) | |
| 2265;35 9: !(T_Exprs_vOut28 _lhsOpps) <- return (inv_Exprs_s29 sem arg28) | |
| 2360;32 9: !(T_Lhs_vOut31 _lhsOpp) <- return (inv_Lhs_s32 sem arg31) | |
| 2685;38 9: !(T_NamedType_vOut34 _lhsOpp) <- return (inv_NamedType_s35 sem arg34) | |
| 2742;40 9: !(T_NamedTypes_vOut37 _lhsOpps) <- return (inv_NamedTypes_s38 sem arg37) | |
| 2821;89 9: !(T_Pattern_vOut40 _lhsOcopy _lhsOisUnderscore _lhsOpp _lhsOpp' _lhsOstrictVars) <- return (inv_Pattern_s41 sem arg40) | |
| 3221;74 9: !(T_Patterns_vOut43 _lhsOcopy _lhsOpps _lhsOpps' _lhsOstrictVars) <- return (inv_Patterns_s44 sem arg43) | |
| 3360;51 9: !(T_Program_vOut46 _lhsOgenIO _lhsOoutput) <- return (inv_Program_s47 sem arg46) | |
| 3523;43 9: !(T_Type_vOut49 _lhsOpp _lhsOprec) <- return (inv_Type_s50 sem arg49) | |
| 4068;35 9: !(T_Types_vOut52 _lhsOpps) <- return (inv_Types_s53 sem arg52) | |
| :uuagc-0.9.52.1/src-generated/PrintErrorMessages.hs | |
| 193;40 9: (T_Error_vOut1 _lhsOme _lhsOpp) <- return (inv_Error_s2 sem arg1) | |
| 1564;33 9: (T_Errors_vOut4 _lhsOpp) <- return (inv_Errors_s5 sem arg4) | |
| :uuagc-0.9.52.1/src-generated/PrintOcamlCode.hs | |
| 88;35 9: !(T_CaseAlt_vOut1 _lhsOpp) <- return (inv_CaseAlt_s2 sem arg1) | |
| 149;37 9: !(T_CaseAlts_vOut4 _lhsOpps) <- return (inv_CaseAlts_s5 sem arg4) | |
| 228;34 9: !(T_Chunk_vOut7 _lhsOpps) <- return (inv_Chunk_s8 sem arg7) | |
| 354;36 9: !(T_Chunks_vOut10 _lhsOpps) <- return (inv_Chunks_s11 sem arg10) | |
| 449;36 9: !(T_DataAlt_vOut13 _lhsOpp) <- return (inv_DataAlt_s14 sem arg13) | |
| 521;38 9: !(T_DataAlts_vOut16 _lhsOpps) <- return (inv_DataAlts_s17 sem arg16) | |
| 592;33 9: !(T_Decl_vOut19 _lhsOpp) <- return (inv_Decl_s20 sem arg19) | |
| 905;35 9: !(T_Decls_vOut22 _lhsOpps) <- return (inv_Decls_s23 sem arg22) | |
| 992;33 9: !(T_Expr_vOut25 _lhsOpp) <- return (inv_Expr_s26 sem arg25) | |
| 1494;35 9: !(T_Exprs_vOut28 _lhsOpps) <- return (inv_Exprs_s29 sem arg28) | |
| 1573;32 9: !(T_Lhs_vOut31 _lhsOpp) <- return (inv_Lhs_s32 sem arg31) | |
| 1741;38 9: !(T_NamedType_vOut34 _lhsOpp) <- return (inv_NamedType_s35 sem arg34) | |
| 1792;40 9: !(T_NamedTypes_vOut37 _lhsOpps) <- return (inv_NamedTypes_s38 sem arg37) | |
| 1863;64 9: !(T_Pattern_vOut40 _lhsOcopy _lhsOisUnderscore _lhsOpp) <- return (inv_Pattern_s41 sem arg40) | |
| 2096;48 9: !(T_Patterns_vOut43 _lhsOcopy _lhsOpps) <- return (inv_Patterns_s44 sem arg43) | |
| 2193;40 9: !(T_Program_vOut46 _lhsOoutput) <- return (inv_Program_s47 sem arg46) | |
| 2259;33 9: !(T_Type_vOut49 _lhsOpp) <- return (inv_Type_s50 sem arg49) | |
| 2603;35 9: !(T_Types_vOut52 _lhsOpps) <- return (inv_Types_s53 sem arg52) | |
| :uuagc-0.9.52.1/src-generated/PrintVisitCode.hs | |
| 73;39 9: (T_CGrammar_vOut1 _lhsOoutput) <- return (inv_CGrammar_s2 sem arg1) | |
| 124;30 9: (T_CInterface_vOut4 ) <- return (inv_CInterface_s5 sem arg4) | |
| 167;32 9: (T_CNonterminal_vOut7 ) <- return (inv_CNonterminal_s8 sem arg7) | |
| 212;34 9: (T_CNonterminals_vOut10 ) <- return (inv_CNonterminals_s11 sem arg10) | |
| 267;32 9: (T_CProduction_vOut13 ) <- return (inv_CProduction_s14 sem arg13) | |
| 310;33 9: (T_CProductions_vOut16 ) <- return (inv_CProductions_s17 sem arg16) | |
| 365;26 9: (T_CRule_vOut19 ) <- return (inv_CRule_s20 sem arg19) | |
| 419;29 9: (T_CSegment_vOut22 ) <- return (inv_CSegment_s23 sem arg22) | |
| 460;30 9: (T_CSegments_vOut25 ) <- return (inv_CSegments_s26 sem arg25) | |
| 515;27 9: (T_CVisit_vOut28 ) <- return (inv_CVisit_s29 sem arg28) | |
| 560;28 9: (T_CVisits_vOut31 ) <- return (inv_CVisits_s32 sem arg31) | |
| 615;31 9: (T_DeclBlocks_vOut34 ) <- return (inv_DeclBlocks_s35 sem arg34) | |
| 669;35 9: (T_DeclBlocksRoot_vOut37 ) <- return (inv_DeclBlocksRoot_s38 sem arg37) | |
| 712;37 9: (T_Pattern_vOut40 _lhsOcopy) <- return (inv_Pattern_s41 sem arg40) | |
| 850;38 9: (T_Patterns_vOut43 _lhsOcopy) <- return (inv_Patterns_s44 sem arg43) | |
| 923;29 9: (T_Sequence_vOut46 ) <- return (inv_Sequence_s47 sem arg46) | |
| :uuagc-0.9.52.1/src-generated/ResolveLocals.hs | |
| 59;63 9: (T_Child_vOut1 _lhsOattributes _lhsOfield _lhsOoutput) <- return (inv_Child_s2 sem arg1) | |
| 149;67 9: (T_Children_vOut4 _lhsOattributes _lhsOfields _lhsOoutput) <- return (inv_Children_s5 sem arg4) | |
| 328;53 9: (T_Expression_vOut7 _lhsOerrors _lhsOoutput) <- return (inv_Expression_s8 sem arg7) | |
| 404;51 9: (T_Grammar_vOut10 _lhsOerrors _lhsOoutput) <- return (inv_Grammar_s11 sem arg10) | |
| 493;92 9: (T_Nonterminal_vOut13 _lhsOerrors _lhsOinhMap' _lhsOnonts _lhsOoutput _lhsOsynMap') <- return (inv_Nonterminal_s14 sem arg13) | |
| 622;93 9: (T_Nonterminals_vOut16 _lhsOerrors _lhsOinhMap' _lhsOnonts _lhsOoutput _lhsOsynMap') <- return (inv_Nonterminals_s17 sem arg16) | |
| 775;88 9: (T_Pattern_vOut19 _lhsOcopy _lhsOerrors _lhsOinstVars _lhsOlocVars _lhsOoutput) <- return (inv_Pattern_s20 sem arg19) | |
| 1107;89 9: (T_Patterns_vOut22 _lhsOcopy _lhsOerrors _lhsOinstVars _lhsOlocVars _lhsOoutput) <- return (inv_Patterns_s23 sem arg22) | |
| 1260;64 9: (T_Production_vOut25 _lhsOcons _lhsOerrors _lhsOoutput) <- return (inv_Production_s26 sem arg25) | |
| 1449;65 9: (T_Productions_vOut28 _lhsOcons _lhsOerrors _lhsOoutput) <- return (inv_Productions_s29 sem arg28) | |
| 1606;75 9: (T_Rule_vOut31 _lhsOerrors _lhsOinstVars _lhsOlocVars _lhsOoutput) <- return (inv_Rule_s32 sem arg31) | |
| 1719;76 9: (T_Rules_vOut34 _lhsOerrors _lhsOinstVars _lhsOlocVars _lhsOoutput) <- return (inv_Rules_s35 sem arg34) | |
| 1894;39 9: (T_TypeSig_vOut37 _lhsOoutput) <- return (inv_TypeSig_s38 sem arg37) | |
| 1944;40 9: (T_TypeSigs_vOut40 _lhsOoutput) <- return (inv_TypeSigs_s41 sem arg40) | |
| :uuagc-0.9.52.1/src-generated/SemHsTokens.hs | |
| 39;106 9: (T_HsToken_vOut1 _lhsOerrors _lhsOoutput _lhsOtok _lhsOusedAttrs _lhsOusedFields _lhsOusedLocals) <- return (inv_HsToken_s2 sem arg1) | |
| 406;107 9: (T_HsTokens_vOut4 _lhsOerrors _lhsOoutput _lhsOtks _lhsOusedAttrs _lhsOusedFields _lhsOusedLocals) <- return (inv_HsTokens_s5 sem arg4) | |
| 591;117 9: (T_HsTokensRoot_vOut7 _lhsOerrors _lhsOoutput _lhsOtextLines _lhsOusedAttrs _lhsOusedFields _lhsOusedLocals) <- return (inv_HsTokensRoot_s8 sem arg7) | |
| :uuagc-0.9.52.1/src-generated/TfmToVisage.hs | |
| 106;36 9: (T_Child_vOut1 _lhsOvchild) <- return (inv_Child_s2 sem arg1) | |
| 179;42 9: (T_Children_vOut4 _lhsOvchildren) <- return (inv_Children_s5 sem arg4) | |
| 274;39 9: (T_Expression_vOut7 _lhsOself) <- return (inv_Expression_s8 sem arg7) | |
| 324;39 9: (T_Grammar_vOut10 _lhsOvisage) <- return (inv_Grammar_s11 sem arg10) | |
| 389;68 9: (T_Nonterminal_vOut13 _lhsOinhMap' _lhsOsynMap' _lhsOvnont) <- return (inv_Nonterminal_s14 sem arg13) | |
| 464;70 9: (T_Nonterminals_vOut16 _lhsOinhMap' _lhsOsynMap' _lhsOvnonts) <- return (inv_Nonterminals_s17 sem arg16) | |
| 571;73 9: (T_Pattern_vOut19 _lhsOcopy _lhsOfieldattrs _lhsOself _lhsOvpat) <- return (inv_Pattern_s20 sem arg19) | |
| 821;75 9: (T_Patterns_vOut22 _lhsOcopy _lhsOfieldattrs _lhsOself _lhsOvpats) <- return (inv_Patterns_s23 sem arg22) | |
| 938;41 9: (T_Production_vOut25 _lhsOvprod) <- return (inv_Production_s26 sem arg25) | |
| 1029;43 9: (T_Productions_vOut28 _lhsOvprods) <- return (inv_Productions_s29 sem arg28) | |
| 1116;35 9: (T_Rule_vOut31 _lhsOvrule) <- return (inv_Rule_s32 sem arg31) | |
| 1169;37 9: (T_Rules_vOut34 _lhsOvrules) <- return (inv_Rules_s35 sem arg34) | |
| 1240;28 9: (T_TypeSig_vOut37 ) <- return (inv_TypeSig_s38 sem arg37) | |
| 1281;29 9: (T_TypeSigs_vOut40 ) <- return (inv_TypeSigs_s41 sem arg40) | |
| :uuagc-0.9.52.1/src-generated/Transform.hs | |
| 522;119 9: (T_AG_vOut1 _lhsOagi _lhsOblocks _lhsOconstructorTypeMap _lhsOerrors _lhsOmoduleDecl _lhsOoutput _lhsOpragmas) <- return (inv_AG_s2 sem arg1) | |
| 1030;145 9: (T_Alt_vOut4 _lhsOcollectedConParams _lhsOcollectedConstraints _lhsOcollectedConstructorNames _lhsOcollectedFields _lhsOcollectedMacros) <- return (inv_Alt_s5 sem arg4) | |
| 1128;146 9: (T_Alts_vOut7 _lhsOcollectedConParams _lhsOcollectedConstraints _lhsOcollectedConstructorNames _lhsOcollectedFields _lhsOcollectedMacros) <- return (inv_Alts_s8 sem arg7) | |
| 1257;75 9: (T_Attrs_vOut10 _lhsOattrDecls _lhsOattrs _lhsOerrors _lhsOuseMap) <- return (inv_Attrs_s11 sem arg10) | |
| 1370;95 9: (T_ConstructorSet_vOut13 _lhsOcollectedConstructorNames _lhsOconstructors _lhsOerrors) <- return (inv_ConstructorSet_s14 sem arg13) | |
| 1527;605 9: (T_Elem_vOut16 _lhsOattrDecls _lhsOattrOrderCollect _lhsOattrs _lhsOblocks _lhsOcollectedArounds _lhsOcollectedAugments _lhsOcollectedConParams _lhsOcollectedConstraints _lhsOcollectedConstructorsMap _lhsOcollectedFields _lhsOcollectedInsts _lhsOcollectedMacros _lhsOcollectedMerges _lhsOcollectedNames _lhsOcollectedRules _lhsOcollectedSetNames _lhsOcollectedSigs _lhsOcollectedUniques _lhsOconstructorTypeMap _lhsOctxCollect _lhsOdefSets _lhsOderivings _lhsOerrors _lhsOmoduleDecl _lhsOparamsCollect _lhsOpragmas _lhsOquantCollect _lhsOsemPragmasCollect _lhsOtypeSyns _lhsOuseMap _lhsOwrappers) <- return (inv_Elem_s17 sem arg16) | |
| 3862;606 9: (T_Elems_vOut19 _lhsOattrDecls _lhsOattrOrderCollect _lhsOattrs _lhsOblocks _lhsOcollectedArounds _lhsOcollectedAugments _lhsOcollectedConParams _lhsOcollectedConstraints _lhsOcollectedConstructorsMap _lhsOcollectedFields _lhsOcollectedInsts _lhsOcollectedMacros _lhsOcollectedMerges _lhsOcollectedNames _lhsOcollectedRules _lhsOcollectedSetNames _lhsOcollectedSigs _lhsOcollectedUniques _lhsOconstructorTypeMap _lhsOctxCollect _lhsOdefSets _lhsOderivings _lhsOerrors _lhsOmoduleDecl _lhsOparamsCollect _lhsOpragmas _lhsOquantCollect _lhsOsemPragmasCollect _lhsOtypeSyns _lhsOuseMap _lhsOwrappers) <- return (inv_Elems_s20 sem arg19) | |
| 4307;72 9: (T_Field_vOut22 _lhsOcollectedConstraints _lhsOcollectedFields) <- return (inv_Field_s23 sem arg22) | |
| 4385;73 9: (T_Fields_vOut25 _lhsOcollectedConstraints _lhsOcollectedFields) <- return (inv_Fields_s26 sem arg25) | |
| 4468;72 9: (T_NontSet_vOut28 _lhsOcollectedNames _lhsOerrors _lhsOnontSet) <- return (inv_NontSet_s29 sem arg28) | |
| 4772;98 9: (T_Pattern_vOut31 _lhsOcopy _lhsOdefinedAttrs _lhsOdefinedInsts _lhsOpatunder _lhsOstpos) <- return (inv_Pattern_s32 sem arg31) | |
| 5043;88 9: (T_Patterns_vOut34 _lhsOcopy _lhsOdefinedAttrs _lhsOdefinedInsts _lhsOpatunder) <- return (inv_Patterns_s35 sem arg34) | |
| 5152;230 9: (T_SemAlt_vOut37 _lhsOattrOrderCollect _lhsOcollectedArounds _lhsOcollectedAugments _lhsOcollectedInsts _lhsOcollectedMerges _lhsOcollectedRules _lhsOcollectedSigs _lhsOcollectedUniques _lhsOerrors _lhsOsemPragmasCollect) <- return (inv_SemAlt_s38 sem arg37) | |
| 5341;231 9: (T_SemAlts_vOut40 _lhsOattrOrderCollect _lhsOcollectedArounds _lhsOcollectedAugments _lhsOcollectedInsts _lhsOcollectedMerges _lhsOcollectedRules _lhsOcollectedSigs _lhsOcollectedUniques _lhsOerrors _lhsOsemPragmasCollect) <- return (inv_SemAlts_s41 sem arg40) | |
| 5536;199 9: (T_SemDef_vOut43 _lhsOaroundInfos _lhsOaugmentInfos _lhsOdefinedInsts _lhsOerrors _lhsOmergeInfos _lhsOorderDepsCollect _lhsOpragmaNamesCollect _lhsOruleInfos _lhsOsigInfos _lhsOuniqueInfos) <- return (inv_SemDef_s44 sem arg43) | |
| 6107;200 9: (T_SemDefs_vOut46 _lhsOaroundInfos _lhsOaugmentInfos _lhsOdefinedInsts _lhsOerrors _lhsOmergeInfos _lhsOorderDepsCollect _lhsOpragmaNamesCollect _lhsOruleInfos _lhsOsigInfos _lhsOuniqueInfos) <- return (inv_SemDefs_s47 sem arg46) | |
| :uuagc-0.9.52.1/src-generated/Visage.hs | |
| 77;40 9: (T_Expression_vOut1 _lhsOaterm) <- return (inv_Expression_s2 sem arg1) | |
| 126;41 9: (T_VisageChild_vOut4 _lhsOaterm) <- return (inv_VisageChild_s5 sem arg4) | |
| 187;45 9: (T_VisageChildren_vOut7 _lhsOaterms) <- return (inv_VisageChildren_s8 sem arg7) | |
| 258;44 9: (T_VisageGrammar_vOut10 _lhsOaterm) <- return (inv_VisageGrammar_s11 sem arg10) | |
| 309;48 9: (T_VisageNonterminal_vOut13 _lhsOaterm) <- return (inv_VisageNonterminal_s14 sem arg13) | |
| 361;50 9: (T_VisageNonterminals_vOut16 _lhsOaterms) <- return (inv_VisageNonterminals_s17 sem arg16) | |
| 432;44 9: (T_VisagePattern_vOut19 _lhsOaterm) <- return (inv_VisagePattern_s20 sem arg19) | |
| 568;46 9: (T_VisagePatterns_vOut22 _lhsOaterms) <- return (inv_VisagePatterns_s23 sem arg22) | |
| 639;47 9: (T_VisageProduction_vOut25 _lhsOaterm) <- return (inv_VisageProduction_s26 sem arg25) | |
| 710;49 9: (T_VisageProductions_vOut28 _lhsOaterms) <- return (inv_VisageProductions_s29 sem arg28) | |
| 781;41 9: (T_VisageRule_vOut31 _lhsOaterm) <- return (inv_VisageRule_s32 sem arg31) | |
| 835;43 9: (T_VisageRules_vOut34 _lhsOaterms) <- return (inv_VisageRules_s35 sem arg34) | |
| :uuagc-bootstrap-0.9.40.2/src/KennedyWarren.hs | |
| 180;35 9:toGVNontDependencyInfo ndi = do dg <- return $ ndgmDepGraph . ndimDepGraph $ ndi | |
| 200;36 9:toGVProdDependencyGraph pdg = do dg <- return $ pdgmDepGraph pdg | |
| :uuagc-bootstrap-0.9.40.2/src/Knuth1.hs | |
| 199;5 9: vs <- return $ Array.indices $ vertexOMap g | |
| 446;41 9: prodGraph <- return $ pdgmDepGraph pdg | |
| 514;40 9: prodGraph <- return $ pdgmDepGraph pdg | |
| :vacuum-opengl-0.0.3/System/Vacuum/OpenGL/Server.hs | |
| 177;11 9: simg <- return eimg -- will be a "scaled image" when i write it | |
| :validations-0.1.0.2/src/Validations/Adapters/Digestive.hs | |
| 20;8 9: es' <- return $ (map (\y -> (absolutePath (fst y) v, snd y)) es) <> (viewErrors v) | |
| :vector-0.11.0.0/tests/Tests/Move.hs | |
| 27;11 9: expected <- return $ basicMove v dstOff srcOff len | |
| 28;9 9: actual <- return $ G.modify (\ mv -> M.move (M.slice dstOff len mv) (M.slice srcOff len mv)) v | |
| :vector-binary-instances-0.2.3.2/Data/Vector/Binary.hs | |
| 93;6 9: v <- return $ unsafePerformIO $ GM.unsafeNew n | |
| 96;21 9: () <- return $ unsafePerformIO $ GM.unsafeWrite v (n-i) x | |
| :vty-5.5.0/test/Verify/Graphics/Vty/Image.hs | |
| 34;10 9: i <- return $ char defAttr 'X' | |
| :vty-examples-5.5.0/Verify/Graphics/Vty/Image.hs | |
| 34;10 9: i <- return $ char defAttr 'X' | |
| :vty-ui-1.9/src/Graphics/Vty/Widgets/Button.hs | |
| 53;4 9: w <- return t >>= | |
| :wai-middleware-crowd-0.1.4/src/Network/Wai/ClientSession.hs | |
| 51;18 9: Right v'' <- return $ B64.decode v' | |
| 52;18 9: Just v''' <- return $ decrypt key v'' | |
| 53;39 9: Right (_, _, Wrapper res expi) <- return $ decodeOrFail $ L.fromStrict v''' | |
| :WashNGo-2.12.0.1/WASH/CGI/Persistent2.hs | |
| 95;7 9: pairs <- return $ read contents | |
| 118;11 9: pairs <- return $ read contents | |
| 129;11 9: pairs <- return $ read contents | |
| 146;11 9: pairs <- return $ read contents | |
| 162;11 9: pairs <- return $ read contents | |
| :weather-api-0.4.3/WeatherApi/WWOnline.hs | |
| 26;13 9: Object c <- return . V.head =<< d .: "current_condition" | |
| :WebBits-2.2/src/BrownPLT/JavaScript/Parser.hs | |
| 419;13 9: [(hex,"")] <- return $ Numeric.readHex digits | |
| :websockets-0.9.6.2/src/Network/WebSockets/Client.hs | |
| 101;17 9: Response _ _ <- return $ finishResponse protocol request response | |
| :wedged-0/Wedged.hs | |
| 308;10 9: Just yx <- return $ topLeft_isEmpty board | |
| :wobsurv-0.1.0/library/Wobsurv/Util/PipesAttoparsec.hs | |
| 34;14 9: chunk <- return . fromMaybe BS.empty =<< lift draw | |
| :xml-conduit-1.3.5/test/main.hs | |
| 608;26 9: Res.Document _ root _ <- return $ Res.parseLBS_ Res.def "<!DOCTYPE foo [<!ENTITY bar \"baz\">]><foo>&bar;</foo>" | |
| 610;27 9: Res.Document _ root2 _ <- return $ Res.parseLBS_ Res.def "<!DOCTYPE foo [<!ENTITY bar \"baz\">]><foo bar='&bar;'/>" | |
| :xml-hamlet-0.4.0.11/Text/Hamlet/XML.hs | |
| 97;23 9: X.Name local mns _ <- return $ fromString s | |
| :xml2x-0.4.2/src/Annotate.hs | |
| 48;22 9: t <- return . goTerms =<< (count opts) 1000 "reading GO terms: " | |
| 104;14 9: k <- return . M.fromList =<< | |
| :xmonad-bluetilebranch-0.9.1.4/XMonad/Main.hsc | |
| 106;41 9: ("--resume" : s : _) <- return args | |
| 111;49 9: ("--resume" : _ : dyns : _) <- return args | |
| :xmonad-contrib-0.12/XMonad/Hooks/Place.hs | |
| 332;10 9: rs <- return (organizeClients ws window floats) | |
| :xmonad-contrib-0.12/XMonad/Hooks/ToggleHook.hs | |
| 112;37 9: (next, all) <- return $ findWithDefault (False, False) n m | |
| :xmonad-contrib-0.12/XMonad/Layout/LayoutBuilder.hs | |
| 187;40 9: l' <- return $ maybe l id ml | |
| :xmonad-contrib-0.12/XMonad/Layout/LayoutBuilderP.hs | |
| 99;40 9: l' <- return $ maybe l id ml | |
| :xmonad-contrib-0.12/XMonad/Layout/SubLayouts.hs | |
| 336;13 9: sls' <- return . Sublayout (I []) defl . map snd <$> fromGroups defl st gs' | |
| :xmonad-contrib-bluetilebranch-0.9.1.4/XMonad/Hooks/Place.hs | |
| 333;10 9: rs <- return (organizeClients ws window floats) | |
| :xmonad-contrib-bluetilebranch-0.9.1.4/XMonad/Layout/LayoutBuilder.hs | |
| 165;40 9: l' <- return $ maybe l id ml | |
| :xmonad-contrib-bluetilebranch-0.9.1.4/XMonad/Layout/SubLayouts.hs | |
| 333;13 9: sls' <- return . Sublayout (I []) defl . map snd <$> fromGroups defl st gs' | |
| :xmonad-extras-0.12.1/XMonad/Config/Alt/Internal.hs | |
| 504;34 9: r <- return $ f ($(varE acc) c) | |
| :xournal-convert-0.1.1/lib/Application/XournalConvert/Convert/MakeSVG.hs | |
| 47;6 9: b <- return . B.any ( == 0 ) . B.take 100 =<< B.hGetContents h | |
| :xournal-parser-0.5.1/src/Text/Xournal/Parse/Zlib.hs | |
| 24;6 9: b <- return . LB.any ( == 0 ) . LB.take 100 =<< LB.hGetContents h | |
| :yackage-0.8.0/yackage.hs | |
| 269;23 9: Just name' <- return $ fromPathPiece name | |
| 274;19 9: Just x <- return $ fromPathPiece s | |
| :yesod-auth-deskcom-1.4.0/src/Yesod/Auth/DeskCom.hs | |
| 264;45 9: [ "to" A..= to | Just to <- return duRedirectTo ] ++ | |
| :yesod-auth-fb-1.7/src/Yesod/Auth/Facebook/ClientSide.hs | |
| 459;18 9: [(expires, "")] <- return $ readsPrec 0 (T.unpack at_expires) | |
| :yesod-core-1.4.20.2/Yesod/Core/Internal/Run.hs | |
| 102;16 9: headers <- return $!! appEndo (ghsHeaders state) [] | |
| :yesod-routes-flow-2.0/Yesod/Routes/Flow/Generator.hs | |
| 108;26 9: Methods _ methods <- return $ resourceDispatch res -- Ignore subsites. | |
| :yhccore-0.9.1/Yhc/Core/FreeVar2.hs | |
| 86;32 9: lhs <- return $ patToExpr lhs | |
| :yhccore-0.9.1/Yhc/Core/Inline.hs | |
| 119;30 9: (CoreFun fn,args) <- return $ fromCoreApp x | |
| 121;17 9: True <- return $ fn `notElem` done | |
| :yi-0.12.5/src/library/Yi/Editor.hs | |
| 374;13 9: updHandler <- return . bufferUpdateHandler =<< ask | |
| :yi-0.12.5/src/library/Yi/Modes.hs | |
| 76;12 9: word <- return $ makeSimpleSearch currentWord | |
| 80;27 9: searchPoint <- return $ regionStart declarationRegion | |
| :yi-0.12.5/src/library/Yi/Snippets.hs | |
| 206;11 9: ms <- return . nub . concat . marks =<< getBufferDyn | |
| :yoko-2.0/Data/Yoko/TH.hs | |
| 533;10 9: matches <- return $ flip map cases $ \(inj, (n, fds)) -> | |
| :yuuko-2010.11.28/src/Yuuko/Text/XML/HXT/XPath/XPathParser.hs | |
| 592;19 9: u <- return $ if null p | |
| :zampolit-0.3/Zampolit.hs | |
| 114;6 9: dir <- return . takeFileName =<< getCurrentDirectory | |
| :zeroth-2009.6.23.3/ListUtils.hs | |
| 11;18 9: (h:t) <- return list | |
| :zlib-bindings-0.1.1.5/test/main.hs | |
| 97;21 9: deflated <- return $ deflateWithDict exampleDict raw | |
| 98;21 9: inflated <- return $ inflateWithDict (S.drop 1 exampleDict) deflated |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment