Function frequency: Difference between revisions

Added FreeBASIC
(Added FreeBASIC)
 
(16 intermediate revisions by 9 users not shown)
Line 10:
 
This will, unfortunately, also catch variable names after an open paren, such as in <code>(let ...)</code> expressions.
<langsyntaxhighlight Lisplang="lisp">(in-package "ACL2")
 
(set-state-ok t)
Line 72:
(invoked-functions "function-freq.lisp" state)
(mv (take 10 (isort-freq-table
(symbol-freq-table fns))) state)))</langsyntaxhighlight>
Output (for itself):
<pre>(((FIRST . 10)
Line 85:
(LIST . 3))
<state>)</pre>
 
=={{header|Arturo}}==
 
<syntaxhighlight lang="rebol">source: to :block read arg\0
frequencies: #[]
 
inspectBlock: function [blk][
loop blk 'item [
case []
when? [word? item][
sItem: to :string item
if set? sItem ->
if function? var sItem [
if? key? frequencies sItem ->
set frequencies sItem (get frequencies sItem)+1
else ->
set frequencies sItem 1
]
]
 
when? [or? block? item
inline? item] ->
inspectBlock item
 
else []
]
]
 
inspectBlock source
 
inspect frequencies</syntaxhighlight>
 
=={{header|AWK}}==
<syntaxhighlight lang="awk">
<lang AWK>
# syntax: GAWK -f FUNCTION_FREQUENCY.AWK filename(s).AWK
#
Line 248 ⟶ 279:
}
}
</syntaxhighlight>
</lang>
<p>Output of running FUNCTION_FREQUENCY.AWK on itself:</p>
<pre>
Line 286 ⟶ 317:
=={{header|BBC BASIC}}==
{{works with|BBC BASIC for Windows}}
<langsyntaxhighlight lang="bbcbasic"> INSTALL @lib$+"SORTLIB"
Sort% = FN_sortinit(1,0) : REM Descending
Line 332 ⟶ 363:
FOR i% = 0 TO C%-1
PRINT func$(i%) " (" ; cnt%(i%) ")"
NEXT</langsyntaxhighlight>
'''Output (for file LBB.BBC):'''
<pre>
Line 349 ⟶ 380:
=={{header|C}}==
This program treats doesn't differentiate between macros and functions. It works by looking for function calls which are not inside strings or comments. If a function call has a C style comment between the opening brace and the name of the function, this program will not recognize it as a function call.
<syntaxhighlight lang="c">
<lang C>
#define _POSIX_SOURCE
#include <ctype.h>
Line 600 ⟶ 631:
}
return 0;
}</langsyntaxhighlight>
 
=={{header|Common Lisp}}==
Loading the file itself before scanning it is the quickest way to determine what function bindings would be created.
<langsyntaxhighlight lang="lisp">(defun mapc-tree (fn tree)
"Apply FN to all elements in TREE."
(cond ((consp tree)
Line 637 ⟶ 668:
(defun top-10 (table)
"Get the top 10 from the source counts TABLE."
(take 10 (sort (hash-to-alist table) '> :key 'cdr)))</langsyntaxhighlight>
{{out}}
<pre>CL-USER> (top-10 (count-source "function-frequency.lisp"))
Line 645 ⟶ 676:
=={{header|Erlang}}==
This is source code analyse. Mainly because I have never done that before.
<syntaxhighlight lang="erlang">
<lang Erlang>
-module( function_frequency ).
 
Line 677 ⟶ 708:
parse_all( _IO, {eof, _End}, Acc ) -> Acc;
parse_all( IO, {ok, Tokens, Location}, Acc ) -> parse_all( IO, io:parse_erl_form(IO, '', Location), [Tokens | Acc] ).
</syntaxhighlight>
</lang>
{{out}}
<pre>
Line 695 ⟶ 726:
=={{header|Factor}}==
Let's take a look at the <code>sequences</code> vocabulary/source file from Factor's standard library. This approach does not count word-defining words such as <code>:</code> and <code>M:</code>, nor does it count words like <code>{</code> and <code>[</code>.
<langsyntaxhighlight lang="factor">USING: accessors kernel math.statistics prettyprint sequences
sequences.deep source-files vocabs words ;
 
Line 701 ⟶ 732:
[ path>source-file top-level-form>> ]
[ vocab-words [ def>> ] [ ] map-as ] bi* compose [ word? ]
deep-filter sorted-histogram <reversed> 7 head .</langsyntaxhighlight>
{{out}}
<pre>
Line 717 ⟶ 748:
=={{header|Forth}}==
Counts colon definitions, variables, constants, words defined by definers like CREATE..DOES>, etc. Check for levels of top from command line, by default 4. GForth 0.7.0 specific.
<langsyntaxhighlight Forthlang="forth">' noop is bootmessage
 
\ --- LIST OF CONSTANTS
Line 876 ⟶ 907:
\ Run, ruuun!
stdin ' run execute-parsing-file DEFS @maxfreq rings-vec over DEFS populate-by args>top# .top bye
</syntaxhighlight>
</lang>
Self test:
<pre>
Line 895 ⟶ 926:
$
</pre>
 
=={{header|FreeBASIC}}==
<syntaxhighlight lang="vbnet">Dim As String code, word, char
Dim As Integer i, j
Dim As String words()
Dim As Integer counts()
 
Open "i:\your_file.bas" For Input As #1
While Not Eof(1)
Line Input #1, code
For i = 1 To Len(code)
char = Lcase(Mid(code, i, 1))
If char >= "a" And char <= "z" Then
word &= Mid(code, i, 1)
Elseif word <> "" Then
For j = 0 To Ubound(words)
If words(j) = word Then
counts(j) += 1
Exit For
End If
Next
If j > Ubound(words) Then
Redim Preserve words(Ubound(words) + 1)
Redim Preserve counts(Ubound(counts) + 1)
words(Ubound(words)) = word
counts(Ubound(counts)) = 1
End If
word = ""
End If
Next
Wend
Close #1
 
For i = 0 To 9
Dim As Integer maxj = 0
For j = 0 To Ubound(counts)
If counts(j) > counts(maxj) Then maxj = j
Next
Print words(maxj); " occurs"; counts(maxj); " times"
counts(maxj) = 0
Next
 
Sleep</syntaxhighlight>
 
=={{header|Go}}==
Only crude approximation is currently easy in Go. The following parses source code, looks for function call syntax (an expression followed by an argument list) and prints the expression.
<langsyntaxhighlight lang="go">package main
 
import (
Line 957 ⟶ 1,031:
func (c calls) Len() int { return len(c) }
func (c calls) Swap(i, j int) { c[i], c[j] = c[j], c[i] }
func (c calls) Less(i, j int) bool { return c[i].count > c[j].count }</langsyntaxhighlight>
Output, when run on source code above:
<pre>
Line 971 ⟶ 1,045:
append 1
</pre>
 
=={{header|Haskell}}==
For functional language with ML-style syntax the given task is really tricky! Functions are everywhere, and the difference between application or using a function as an argument or operand -- is question of semantics, not syntax.
Nevertheless, the quick and dirty solution may be given. It finds explicit applications which are distinguished as applications in AST while parsing the Haskell code. As soon as one will try to make this solution cleaner or more precise, ambiguity of the task will emerge immediately.
 
<syntaxhighlight lang="haskell">import Language.Haskell.Parser (parseModule)
import Data.List.Split (splitOn)
import Data.List (nub, sortOn, elemIndices)
 
findApps src = freq $ concat [apps, comps]
where
ast = show $ parseModule src
apps = extract <$> splitApp ast
comps = extract <$> concat (splitComp <$> splitInfix ast)
splitApp = tail . splitOn "(HsApp (HsVar (UnQual (HsIdent \""
splitInfix = tail . splitOn "(HsInfixApp (HsVar (UnQual (HsIdent \""
splitComp = take 1 . splitOn "(HsQVarOp (UnQual (HsSymbol \""
extract = takeWhile (/= '\"')
freq lst = [ (count x lst, x) | x <- nub lst ]
count x = length . elemIndices x
 
main = do
src <- readFile "CountFunctions.hs"
let res = sortOn (negate . fst) $ findApps src
mapM_ (\(n, f) -> putStrLn $ show n ++ "\t" ++ f) res</syntaxhighlight>
 
<pre>*Main> main
3 splitOn
2 concat
2 show
2 extract
2 tail
1 parseModule
1 splitApp
1 splitInfix
1 take
1 takeWhile
1 count
1 nub
1 elemIndices
1 readFile
1 sortOn
1 findApps
1 mapM_
1 freq
1 splitComp
1 length
1 negate
1 putStrLn</pre>
 
=={{header|J}}==
The lowest approach taken here makes no effort to classify the primitives as monads nor dyads, nor as verbs, adverbs, nor conjunctions. Did "-" mean "additive inverse" or indicate subtraction? Does ";" raze or link? J is a multi-instruction single data language. Parentheses around a group of verbs form hooks or forks which affect data flow. The simple top10 verb does not find these important constructs. So we shall ignore them for this exercise.
 
<syntaxhighlight lang="j">
<lang j>
IGNORE=: ;:'y(0)1',CR
 
Line 1,011 ⟶ 1,134:
│14655│@ │
└─────┴──┘
</syntaxhighlight>
</lang>
 
=={{header|Julia}}==
{{works with|Julia|0.6}}
 
<langsyntaxhighlight lang="julia">using Printf, DataStructures
 
function funcfreqs(expr::Expr)
Line 1,048 ⟶ 1,171:
for (v, f) in freqs
@printf("%10s → %i\n", v, f)
end</langsyntaxhighlight>
 
{{out}}
Line 1,073 ⟶ 1,196:
=={{header|LiveCode}}==
Initially based on [http://lessons.livecode.com/m/2592/l/126343-listing-all-the-handlers-in-a-script Listing all the handlers in a script]
<langsyntaxhighlight LiveCodelang="livecode">function handlerNames pScript
put pScript into pScriptCopy
filter pScript with regex pattern "^(on|function).*"
Line 1,101 ⟶ 1,224:
put line 1 to 10 of handlers into handlers
return handlers
end handlerNames</langsyntaxhighlight>
 
To use<langsyntaxhighlight LiveCodelang="livecode">put handlerNames(the script of this stack & cr & the script of this card & cr & the script of me)</langsyntaxhighlight>
 
Sample output<langsyntaxhighlight LiveCodelang="livecode">if 8
put 8
return 8
Line 1,114 ⟶ 1,237:
factorial 2 -- user def function for other rosetta task
factorialit 2 -- user def function for other rosetta task
mouseUp 2</langsyntaxhighlight>
 
=={{header|Mathematica}} / {{header|Wolfram Language}}==
<langsyntaxhighlight Mathematicalang="mathematica">programCount[fn_] := Reverse[If[Length[#] > 10, Take[#, -10], #] &[SortBy[Tally[Cases[DownValues[fn], s_Symbol, \[Infinity], Heads -> True]], Last]]]</langsyntaxhighlight>
{{out}}The output of applying this program to itself...<pre>programCount[programCount]
 
{{Slot, 3}, {Pattern, 2}, {fn, 2}, {Blank, 2}, {\[Infinity], 1}, {True, 1}, {Tally, 1}, {Take, 1}, {Symbol, 1}, {SortBy, 1}}</pre>
 
=={{header|Nim}}==
<syntaxhighlight lang="nim"># naive function calling counter
# TODO consider a more sophisticated condition on counting function callings
# without parenthesis which are common in nim lang. Be aware that the AST of
# object accessor and procedure calling without parenthesis are same.
 
import macros, tables, strformat, os
proc visitCall(node: NimNode, table: CountTableRef) =
if node.kind == nnkCall:
if node[0].kind == nnkDotExpr:
table.inc($node[0][1])
visitCall(node[0][0], table)
else:
if node[0].kind == nnkBracketExpr:
if node[0][0].kind == nnkDotExpr:
table.inc($node[0][0][1])
visitCall(node[0][0][0], table)
return
else:
table.inc($node[0][0])
if len(node[0]) > 1:
for child in node[0][1..^1]:
visitCall(child, table)
elif node[0].kind == nnkPar:
visitCall(node[0], table)
else:
table.inc($node[0])
if len(node) > 1:
for child in node[1..^1]:
visitCall(child, table)
else:
for child in node.children():
visitCall(child, table)
 
static:
const code = staticRead(expandTilde(&"~/.choosenim/toolchains/nim-{NimVersion}/lib/system.nim"))
var
ast = parseStmt(code)
callCounts = newCountTable[string]()
ast.visitCall(callCounts)
sort(callCounts)
var total = 10
for ident, times in callCounts.pairs():
echo(&"{ident} called {times} times")
total-=1
if total == 0:
break</syntaxhighlight>
{{out}}
<pre>
defined called 133 times
add called 16 times
declared called 13 times
newSeq called 11 times
int called 10 times
setLen called 9 times
type called 8 times
compileOption called 8 times
uint called 8 times
move called 7 times
</pre>
 
=={{header|Perl}}==
We leverage the PPI::Tokenizer module.
<langsyntaxhighlight lang="perl">use PPI::Tokenizer;
my $Tokenizer = PPI::Tokenizer->new( '/path/to/your/script.pl' );
my %counts;
Line 1,139 ⟶ 1,323:
foreach my $token (@top_ten_by_occurrence) {
print $counts{$token}, "\t", $token, "\n";
}</langsyntaxhighlight>
{{out}}
When run on itself:
Line 1,156 ⟶ 1,340:
As Phix is self hosted, we can modify the compiler (or a copy of it) directly for this task.<br>
Add the line shown to procedure Call() in pmain.e, after the else on line 4938 (at the time of writing)
<!--<syntaxhighlight lang="phix">(notonline)-->
<pre>
<span style="color: #008080;">else</span> <span style="color: #000080;font-style:italic;">-- rType=FUNC|TYPE</span>
<span style="color: #000000;">log_function_call</span><span style="color: #0000FF;">(</span><span style="color: #000000;">rtnNo</span><span style="color: #0000FF;">)</span>
log_function_call(rtnNo)
<!--</syntaxhighlight>-->
</pre>
(I may have been a bit too literal about "function" here, specifically "not procedure")
 
Now create our test.exw program, which wraps the entire compiler:
<!--<syntaxhighlight lang="phix">(notonline)-->
<lang Phix>constant func_log = new_dict(),
<span style="color: #008080;">without</span> <span style="color: #008080;">js</span> <span style="color: #000080;font-style:italic;">-- file i/o, etc...</span>
func_freq = new_dict()
<span style="color: #008080;">constant</span> <span style="color: #000000;">func_log</span> <span style="color: #0000FF;">=</span> <span style="color: #7060A8;">new_dict</span><span style="color: #0000FF;">(),</span>
 
<span style="color: #000000;">func_freq</span> <span style="color: #0000FF;">=</span> <span style="color: #7060A8;">new_dict</span><span style="color: #0000FF;">()</span>
global procedure log_function_call(integer rtnNo)
integer node = getd_index(rtnNo,func_log)
<span style="color: #008080;">global</span> <span style="color: #008080;">procedure</span> <span style="color: #000000;">log_function_call</span><span style="color: #0000FF;">(</span><span style="color: #004080;">integer</span> <span style="color: #000000;">rtnNo</span><span style="color: #0000FF;">)</span>
setd(rtnNo,iff(node=NULL?1:getd_by_index(node,func_log)+1),func_log)
<span style="color: #004080;">integer</span> <span style="color: #000000;">node</span> <span style="color: #0000FF;">=</span> <span style="color: #7060A8;">getd_index</span><span style="color: #0000FF;">(</span><span style="color: #000000;">rtnNo</span><span style="color: #0000FF;">,</span><span style="color: #000000;">func_log</span><span style="color: #0000FF;">)</span>
end procedure
<span style="color: #7060A8;">setd</span><span style="color: #0000FF;">(</span><span style="color: #000000;">rtnNo</span><span style="color: #0000FF;">,</span><span style="color: #008080;">iff</span><span style="color: #0000FF;">(</span><span style="color: #000000;">node</span><span style="color: #0000FF;">=</span><span style="color: #004600;">NULL</span><span style="color: #0000FF;">?</span><span style="color: #000000;">1</span><span style="color: #0000FF;">:</span><span style="color: #7060A8;">getd_by_index</span><span style="color: #0000FF;">(</span><span style="color: #000000;">node</span><span style="color: #0000FF;">,</span><span style="color: #000000;">func_log</span><span style="color: #0000FF;">)+</span><span style="color: #000000;">1</span><span style="color: #0000FF;">),</span><span style="color: #000000;">func_log</span><span style="color: #0000FF;">)</span>
 
<span style="color: #008080;">end</span> <span style="color: #008080;">procedure</span>
include p.exw -- the phix compiler, full source
 
<span style="color: #008080;">include</span> <span style="color: #000000;">p</span><span style="color: #0000FF;">.</span><span style="color: #000000;">exw</span> <span style="color: #000080;font-style:italic;">-- the phix compiler, full source
-- invert the dictionary, then print top ten
 
-- invert the dictionary, then print top ten</span>
integer count = 0
function visitor(object key, integer data, integer user_data)
<span style="color: #004080;">integer</span> <span style="color: #000000;">count</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">0</span>
if user_data=1 then -- invert
<span style="color: #008080;">function</span> <span style="color: #000000;">visitor</span><span style="color: #0000FF;">(</span><span style="color: #004080;">object</span> <span style="color: #000000;">key</span><span style="color: #0000FF;">,</span> <span style="color: #004080;">integer</span> <span style="color: #000000;">data</span><span style="color: #0000FF;">,</span> <span style="color: #004080;">integer</span> <span style="color: #000000;">user_data</span><span style="color: #0000FF;">)</span>
setd({data,key},0,func_freq)
<span style="color: #008080;">if</span> <span style="color: #000000;">user_data</span><span style="color: #0000FF;">=</span><span style="color: #000000;">1</span> <span style="color: #008080;">then</span> <span style="color: #000080;font-style:italic;">-- invert</span>
else
<span style="color: #7060A8;">setd</span><span style="color: #0000FF;">({</span><span style="color: #000000;">data</span><span style="color: #0000FF;">,</span><span style="color: #000000;">key</span><span style="color: #0000FF;">},</span><span style="color: #000000;">0</span><span style="color: #0000FF;">,</span><span style="color: #000000;">func_freq</span><span style="color: #0000FF;">)</span>
key[2] = symtab[key[2]][S_Name]
<span style="color: #008080;">else</span>
?key
<span style="color: #000000;">key</span><span style="color: #0000FF;">[</span><span style="color: #000000;">2</span><span style="color: #0000FF;">]</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">symtab</span><span style="color: #0000FF;">[</span><span style="color: #000000;">key</span><span style="color: #0000FF;">[</span><span style="color: #000000;">2</span><span style="color: #0000FF;">]][</span><span style="color: #000000;">S_Name</span><span style="color: #0000FF;">]</span>
count += 1
<span style="color: #0000FF;">?</span><span style="color: #000000;">key</span>
if count>10 then return 0 end if -- cease traversal
<span style="color: #000000;">count</span> <span style="color: #0000FF;">+=</span> <span style="color: #000000;">1</span>
end if
<span style="color: #008080;">if</span> <span style="color: #000000;">count</span><span style="color: #0000FF;">></span><span style="color: #000000;">10</span> <span style="color: #008080;">then</span> <span style="color: #008080;">return</span> <span style="color: #000000;">0</span> <span style="color: #008080;">end</span> <span style="color: #008080;">if</span> <span style="color: #000080;font-style:italic;">-- cease traversal</span>
return 1
<span style="color: #008080;">end</span> <span style="color: #008080;">if</span>
end function
<span style="color: #008080;">return</span> <span style="color: #000000;">1</span>
constant r_visitor = routine_id("visitor")
<span style="color: #008080;">end</span> <span style="color: #008080;">function</span>
 
rebuild_callback() -- (convert ternary tree indexes to readable names)
<span style="color: #000000;">rebuild_callback</span><span style="color: #0000FF;">()</span> <span style="color: #000080;font-style:italic;">-- (convert ternary tree indexes to readable names)</span>
 
traverse_dict(r_visitor,1,func_log) -- invert
<span style="color: #7060A8;">traverse_dict</span><span style="color: #0000FF;">(</span><span style="color: #000000;">visitor</span><span style="color: #0000FF;">,</span><span style="color: #000000;">1</span><span style="color: #0000FF;">,</span><span style="color: #000000;">func_log</span><span style="color: #0000FF;">)</span> <span style="color: #000080;font-style:italic;">-- invert</span>
traverse_dict(r_visitor,2,func_freq,rev:=true) -- top 10</lang>
<span style="color: #7060A8;">traverse_dict</span><span style="color: #0000FF;">(</span><span style="color: #000000;">visitor</span><span style="color: #0000FF;">,</span><span style="color: #000000;">2</span><span style="color: #0000FF;">,</span><span style="color: #000000;">func_freq</span><span style="color: #0000FF;">,</span><span style="color: #000000;">rev</span><span style="color: #0000FF;">:=</span><span style="color: #004600;">true</span><span style="color: #0000FF;">)</span> <span style="color: #000080;font-style:italic;">-- top 10</span>
<!--</syntaxhighlight>-->
Invoke using "p test -norun test" (note you can omit the ".exw" part of "test.exw")
{{out}}
Line 1,223 ⟶ 1,409:
 
=={{header|PicoLisp}}==
<langsyntaxhighlight PicoLisplang="picolisp">(let Freq NIL
(for "L" (filter pair (extract getd (all)))
(for "F"
Line 1,231 ⟶ 1,417:
(accu 'Freq "F" 1) ) )
(for X (head 10 (flip (by cdr sort Freq)))
(tab (-7 4) (car X) (cdr X)) ) )</langsyntaxhighlight>
Output, for the system in debug mode plus the above code:
<pre>quote 310
Line 1,269 ⟶ 1,455:
{{works with|Python|3.x}}
This code parses a Python source file using the built-in '''ast''' module and counts simple function calls; it won't process method calls or cases when you call the result of an expression. Also, since constructors are invoked by calling the class, constructor calls are counted as well.
<langsyntaxhighlight lang="python">import ast
 
class CallCountingVisitor(ast.NodeVisitor):
Line 1,292 ⟶ 1,478:
for name, count in top10:
print(name,'called',count,'times')
</syntaxhighlight>
</lang>
 
The result of running the program on the ftplib module of Python 3.2:
Line 1,309 ⟶ 1,495:
 
=={{header|Racket}}==
<langsyntaxhighlight lang="racket">
#lang racket
(require math)
Line 1,318 ⟶ 1,504:
(define counts (sort (hash->list (samples->hash symbols)) >= #:key cdr))
(take counts (min 10 (length counts)))
</syntaxhighlight>
</lang>
Output:
<langsyntaxhighlight lang="racket">
'((define . 4)
(counts . 3)
Line 1,331 ⟶ 1,517:
(in-port . 1)
(sort . 1))
</syntaxhighlight>
</lang>
 
=={{header|Raku}}==
(formerly Perl 6)
Here we just examine the ast of the Raku compiler (which is written in Raku) to look for function calls.
<syntaxhighlight lang="raku" perl6line>my $text = qqx[raku --target=ast @*ARGS[]];
my %fun;
for $text.lines {
Line 1,342 ⟶ 1,528:
}
 
for %fun.invert.sort.reverse[^10] { .value.say }</langsyntaxhighlight>
{{out}}
Here we run it on the strand sort RC entry. Note how Raku considers various operators to really be function calls underneath.
Line 1,360 ⟶ 1,546:
===version 1===
This program counts statically. It lacks, however, treatment of comments and literal strings.
<langsyntaxhighlight lang="rexx">fid='pgm.rex'
cnt.=0
funl=''
Line 1,393 ⟶ 1,579:
If cnt.fun=1 Then
funl=funl fun
Return</langsyntaxhighlight>
{{out}}
<pre> 1 lines
Line 1,415 ⟶ 1,601:
Contents of comments and literal strings are not analyzed.
Neither are function invocations via CALL.
<langsyntaxhighlight lang="rexx">/* REXX ****************************************** Version 11.12.2015 **
* Rexx Tokenizer to find function invocations
*-----------------------------------------------------------------------
Line 1,924 ⟶ 2,110:
End
If errtxt<>'' Then Say ' 'errtxt
Exit 12</langsyntaxhighlight>
{{out}}
Result for the above program.
Line 1,949 ⟶ 2,135:
1 wordsort
0.093000 seconds elapsed for 2200 tokens in 510 lines.</pre>
 
=={{header|RPL}}==
« DUP 1 DUP SUB ROT SWAP + → seps input
« { }
1 input SIZE '''FOR''' j
1 OVER TYPE 5 == ::SF ::CF IFTE
input j DUP SUB
seps OVER POS ::DROP IFT
1 FC? ::+ IFT
'''NEXT'''
» » '<span style="color:blue">TOKNZ</span>' STO <span style="color:grey">''@ ("input" "seps" → { "tokens" } )''</span>
« RCL →STR " /n" <span style="color:blue">TOKNZ</span> → tokens <span style="color:grey">''@ "/n" means "new line" character ''</span>
« { { 0 "" } }
1 tokens SIZE '''FOR''' j
tokens j GET "'" SWAP OVER + +
'''IFERR''' STR→ '''THEN'''
2 OVER SIZE 1 - SUB
'''IF''' "{}][()" OVER POS <span style="color:grey">''@ exclude separators from the count''</span>
'''THEN''' DROP
'''ELSE'''
OVER 1 « 2 GET » DOLIST
'''IF''' OVER POS
'''THEN''' LASTARG SWAP DROP DUP2 GET { 1 "" } ADD PUT
'''ELSE''' 1 SWAP 2 →LIST 1 →LIST + END
'''ELSE''' DROP '''END'''
'''END'''
'''NEXT'''
SORT REVLIST 1 10 SUB
1 « EVAL →TAG » DOLIST
» » '<span style="color:blue">FNFREQ</span>' STO <span style="color:grey">''@ ( 'program' → { :word: occ .. :word: occ } ''</span>
 
'<span style="color:blue">FNFREQ</span>' <span style="color:blue">FNFREQ</span>
{{out}}
<pre>
1: { :OVER: 5 :»: 4 :«: 4 :END: 3 :ELSE: 3 :DROP: 3 :THEN: 3 :+: 3 :SWAP: 3 :GET: 3 }
</pre>
 
=={{header|Sidef}}==
Sidef provides full access to its parser, allowing us to inspect all the declarations within a program.
<langsyntaxhighlight lang="ruby">func foo { }
func bar { }
 
Line 1,965 ⟶ 2,188:
" #{entry{:line}}) is used #{entry{:count}} times")
}
}</langsyntaxhighlight>
 
{{out}}
Line 1,975 ⟶ 2,198:
=={{header|Smalltalk}}==
{{works with|Smalltalk/X}}
This parses all classes of all loaded packages/libraries (takes a few seconds);. From the resultscode, belowit areshould printedbe inobvious scriptinghow mode,to whererestrict onlythe asearch smallto partpackages, of thelibraries, systemclasses isor actuallyindividual preloadedmethods.
 
<langsyntaxhighlight lang="smalltalk">bagOfCalls := Bag new.
Smalltalk allClassesDo:[:cls |
cls instAndClassMethodsDo:[:mthd |
Line 1,985 ⟶ 2,208:
(bagOfCalls sortedCounts to:10) do:[:assoc |
Stdout printCR: e'method {assoc value} is called {assoc key} times.'
].</langsyntaxhighlight>
note: messagesSent calls the parser for an AST and enumerates the parse nodes; it does not know, which get inlined and which end up being called actually (in fact, most of the one's below are probably inlined).
 
The results below were printed in scripting mode, where only a small part of the system is actually preloaded.
{{out}}
<pre>method ifTrue:is called 19805 times.
Line 2,000 ⟶ 2,225:
 
=={{header|Tcl}}==
<langsyntaxhighlight lang="tcl">package require Tcl 8.6
 
proc examine {filename} {
Line 2,027 ⟶ 2,252:
foreach {cmd count} [lrange $cmdinfo 0 19] {
puts [format "%-20s%d" $cmd $count]
}</langsyntaxhighlight>
Sample run (note that the commands found are all standard Tcl commands; they're ''just'' commands so it is natural to expect them to be found):
<pre>
Line 2,042 ⟶ 2,267:
lappend 351
</pre><!-- note that it's certainly possible that not all commands are found; break and continue are likely underrepresented -->
 
=={{header|Wren}}==
{{libheader|Wren-pattern}}
{{libheader|Wren-set}}
{{libheader|Wren-sort}}
{{libheader|Wren-fmt}}
Wren distinguishes between functions and methods.
 
The former are first-class standalone objects whereas the latter are always members of a class and can be either instance or static.
 
Functions are always invoked by their call() method.
 
Some kinds of methods (getters, setters and operators) are not followed by an argument list but, in the interests of simplicity, we only count 'function methods' i.e. methods which are followed by a (possibly empty) argument list for the purposes of this task.
 
In the absence of any other feasible approach, we simply search for method/function calls in a given Wren source file and count them to find the 'top ten'.
<syntaxhighlight lang="wren">import "io" for File
import "os" for Process
import "./pattern" for Pattern
import "./set" for Bag
import "./sort" for Sort
import "./fmt" for Fmt
 
var args = Process.arguments
if (args.count != 1) {
Fiber.abort("There should be exactly one argument - the file path to be analyzed")
}
var p = Pattern.new("[+1/x.+1/x](")
var source = File.read(args[0])
var matches = p.findAll(source)
var bag = Bag.new(matches.map { |m| m.captures[0].text })
var methodCalls = bag.toMap.toList
var cmp = Fn.new { |i, j| (j.value - i.value).sign }
Sort.quick(methodCalls, 0, methodCalls.count-1, cmp)
System.print("Top ten method/function calls in %(args[0]):\n")
System.print("Called Method/Function")
System.print("------ ----------------")
for (mc in methodCalls.take(10)) {
Fmt.print(" $2d $s", mc.value, mc.key)
}</syntaxhighlight>
 
{{out}}
Using the source file for the [https://rosettacode.org/wiki/Catmull%E2%80%93Clark_subdivision_surface#Wren Catmull-Clark task] as an example:
<pre>
Top ten method/function calls in catmull_clark.wren:
 
Called Method/Function
------ ----------------
13 Point.new
8 List.filled
6 sumPoint.call
5 Int.cantorPair
4 mulPoint.call
4 switchNums.call
4 newFaces.add
4 divPoint.call
3 mergedEdges.add
3 centerPoint.call
</pre>
 
=={{header|XPL0}}==
This program lists its top ten intrinsic (code) calls.
The included xpllib provides many such calls.
Intrinsics are routines built into the runtime support code.
<syntaxhighlight lang "XPL0">
\codesr.xpl Complete set of intrinsics for XPL0 on the Raspberry Pi
code \var:=\Abs(int)=0, \var:=\Ran(range)=1,
\var:=\Rem(expr)=2, \adr:=\Reserve(bytes)=3,
\var:=\Swap(int)=4, \var:=\Extend(byte)=5,
Restart=6, \var:=\ChIn(dev)=7,
ChOut(dev,byte)=8, CrLf(dev)=9,
\var:=\IntIn(dev)=10, IntOut(dev,int)=11,
Text(dev,str)=12, OpenI(dev)=13,
OpenO(dev)=14, Close(dev)=15,
Abort=16, Trap(bits)=17,
\var:=\Free=18, \var:=\Rerun=19,
\adr:=\GetHP=20, SetHP(adr)=21,
\var:=\GetErr=22, Cursor(X,Y)=23,
FSet(hand,^I/^O)=24, SetRun(bool)=25,
\var:=\HexIn(dev)=26, HexOut(dev,int)=27,
\var:=\FOpen(pathname,0=r/1=w)=29, FClose(hand)=32,
\var:=\KeyHit=33, \var:=\ChkKey=33,
Sound(vol,dur,period)=39, Clear=40,
Point(X,Y,color)=41, Line(X,Y,color)=42,
Move(X,Y)=43, \var:=\ReadPix(X,Y)=44,
SetVid(mode)=45, \var:=\Fix(real)=50,
Attrib(bg:fg)=69, SetWind(X0,Y0,X1,Y1,mode,fill)=70,
RawText(dev,str)=71, Hilight(X0,Y0,X1,Y1,bg:fg)=72,
\adr:=\MAlloc(bytes)=73, Release(adr)=74,
TrapC(bool)=75, \var:=\TestC=76,
ShowMouse(bool)=77, MoveMouse=78,
RanSeed(int)=79, \rgb:=\GetPalette(reg)=80,
Paint(X,Y,W,H,image,W2)=81, \var:=\GetTime=82,
BackUp=83, SetFB(W,H,D)=84,
\var:=\OpenMouse=85, \adr:=\GetMouse=86,
\adr:=\GetMouseMove=87, ShowCursor(bool)=88,
\var:=\GetKey=89, SetPalette(reg,R,G,B)=90,
\adr:=\GetFont(set)=91, SetFont(height,adr)=92,
\var:=\GetShiftKeys=93, DelayUS(int)=94,
\adr:=\GetDateTime=95, InsertKey(byte)=96,
\adr:=\GetFB=97, WaitForVSync=98,
ShowPage(0/1)=99, CopyMem(dst,src,bytes)=100,
FillMem(adr,byte,bytes)=101, \adr:=\ReallocMem(adr,bytes)=102,
PlaySoundFile(pathname)=103, SetHexDigits(digits)=104,
\process:=\Fork(processes)=105, Join(process)=106,
\adr:=\SharedMem(bytes)=107, Lock(adr)=108,
Unlock(adr)=109;
code real
\adr:=\RlRes(int)=46, \var:=\RlIn(dev)=47,
RlOut(dev,real)=48, \var:=\Float(int)=49,
\var:=\RlAbs(real)=51, Format(int,int)=52,
\var:=\Sqrt(real)=53, \var:=\Ln(real)=54,
\var:=\Exp(real)=55, \var:=\Sin(real)=56,
\var:=\ATan2(realY,realX)=57, \var:=\Mod(real,real)=58,
\var:=\Log(real)=59, \var:=\Cos(real)=60,
\var:=\Tan(real)=61, \var:=\ASin(real)=62,
\var:=\ACos(real)=63, \var:=\Floor(real)=64,
\var:=\Ceil(real)=65, \var:=\Pow(realX,realY)=66;
 
include xpllib;
 
int Counts(128), I, Ch, Num, Maxx, SI Cnt;
char Str, Addr;
 
[\Read this program's compiled assembly language into a string
if not OpenInFile("funcfreq.s") then
[Text(0, "funcfreq.s not found"); exit 1];
Str:= 0; I:= 0;
loop [Str:= ReallocMem(Str, I+1);
Ch:= ChIn(3);
if Ch = EOF then quit;
Str(I):= Ch;
I:= I+1;
];
Str(I):= 0;
 
\Count numbers of times each intrinsic is called
for I:= 0 to 127 do Counts(I):= 0;
Addr:= Str;
loop [Addr:= StrFind(Addr, "intr");
if Addr = 0 then quit;
Addr:= Addr+4; \skip "intr"
Num:= 0;
while Addr(0)>=^0 and Addr(0)<=^9 do
[Num:= Num*10 + Addr(0) - ^0;
Addr:= Addr+1;
];
if Num < 128 then \for safety
Counts(Num):= Counts(Num)+1;
];
 
Print("Top ten intrinsic calls (code: freq):\n");
Cnt:= 0;
loop [Maxx:= 0;
for I:= 0 to 127 do
if Counts(I) > Maxx then
[Maxx:= Counts(I);
SI:= I;
];
Print("%2d: %2d\n", SI, Counts(SI));
Counts(SI):= 0;
Cnt:= Cnt+1;
if Cnt >= 10 then quit;
];
]</syntaxhighlight>
{{out}}
<pre>
Top ten intrinsic calls (code: freq):
8: 72
7: 67
41: 14
11: 12
13: 12
12: 11
14: 10
48: 10
42: 9
43: 9
</pre>
2,122

edits