Skip to content
GitLab
Explore
Sign in
Register
Primary navigation
Search or go to…
Project
H
hpc-bin
Manage
Activity
Members
Labels
Plan
Issues
Issue boards
Milestones
Wiki
Requirements
Code
Merge requests
Repository
Branches
Commits
Tags
Repository graph
Compare revisions
Snippets
Locked files
Build
Pipelines
Jobs
Pipeline schedules
Test cases
Artifacts
Deploy
Releases
Package Registry
Container Registry
Model registry
Operate
Environments
Terraform modules
Monitor
Incidents
Analyze
Value stream analytics
Contributor analytics
CI/CD analytics
Repository analytics
Code review analytics
Issue analytics
Insights
Model experiments
Help
Help
Support
GitLab documentation
Compare GitLab plans
Community forum
Contribute to GitLab
Provide feedback
Terms and privacy
Keyboard shortcuts
?
Snippets
Groups
Projects
Show more breadcrumbs
Georgy Lukyanov
hpc-bin
Commits
c67a6ae2
Commit
c67a6ae2
authored
1 year ago
by
BinderDavid
Browse files
Options
Downloads
Patches
Plain Diff
Refactor ShowTix and add export list to Lexer
parent
6c3a4ea0
No related branches found
No related tags found
No related merge requests found
Changes
2
Hide whitespace changes
Inline
Side-by-side
Showing
2 changed files
src/Trace/Hpc/Lexer.hs
+2
-9
2 additions, 9 deletions
src/Trace/Hpc/Lexer.hs
src/Trace/Hpc/ShowTix.hs
+62
-34
62 additions, 34 deletions
src/Trace/Hpc/ShowTix.hs
with
64 additions
and
43 deletions
src/Trace/Hpc/Lexer.hs
+
2
−
9
View file @
c67a6ae2
...
@@ -2,11 +2,9 @@
...
@@ -2,11 +2,9 @@
-- Module : Trace.Hpc.Lexer
-- Module : Trace.Hpc.Lexer
-- Description : A lexer for overlay files use by @hpc overlay@
-- Description : A lexer for overlay files use by @hpc overlay@
-- License : BSD-3-Clause
-- License : BSD-3-Clause
module
Trace.Hpc.Lexer
where
module
Trace.Hpc.Lexer
(
Token
(
..
),
initLexer
)
where
import
Data.Char
import
Data.Char
(
isAlpha
,
isDigit
,
isSpace
)
------------------------------------------------------------------------------
data
Token
data
Token
=
ID
String
=
ID
String
...
@@ -55,8 +53,3 @@ lexerCAT (c : cs) s line column
...
@@ -55,8 +53,3 @@ lexerCAT (c : cs) s line column
|
c
==
']'
=
(
line
,
column
,
CAT
s
)
:
lexer
cs
line
(
succ
column
)
|
c
==
']'
=
(
line
,
column
,
CAT
s
)
:
lexer
cs
line
(
succ
column
)
|
otherwise
=
lexerCAT
cs
(
s
++
[
c
])
line
(
succ
column
)
|
otherwise
=
lexerCAT
cs
(
s
++
[
c
])
line
(
succ
column
)
lexerCAT
[]
_
_
_
=
error
"lexer failure in CAT"
lexerCAT
[]
_
_
_
=
error
"lexer failure in CAT"
test
::
IO
()
test
=
do
t
<-
readFile
"EXAMPLE.tc"
print
(
initLexer
t
)
This diff is collapsed.
Click to expand it.
src/Trace/Hpc/ShowTix.hs
+
62
−
34
View file @
c67a6ae2
...
@@ -4,13 +4,30 @@
...
@@ -4,13 +4,30 @@
-- License : BSD-3-Clause
-- License : BSD-3-Clause
module
Trace.Hpc.ShowTix
(
showtixPlugin
)
where
module
Trace.Hpc.ShowTix
(
showtixPlugin
)
where
import
Control.Monad
(
forM
,
forM_
)
import
qualified
Data.Set
as
Set
import
qualified
Data.Set
as
Set
import
Trace.Hpc.Flags
import
Trace.Hpc.Flags
import
Trace.Hpc.Mix
(
FlagOptSeq
,
import
Trace.Hpc.Plugin
Flags
(
includeMods
),
allowModule
,
excludeOpt
,
hpcDirOpt
,
includeOpt
,
outputOpt
,
readMixWithFlags
,
resetHpcDirsOpt
,
srcDirOpt
,
verbosityOpt
,
)
import
Trace.Hpc.Mix
(
Mix
(
..
),
MixEntry
)
import
Trace.Hpc.Plugin
(
Plugin
(
..
),
hpcError
)
import
Trace.Hpc.Tix
import
Trace.Hpc.Tix
(
Tix
(
Tix
),
------------------------------------------------------------------------------
TixModule
(
..
),
getTixFileName
,
readTix
,
tixModuleName
,
)
showtixOptions
::
FlagOptSeq
showtixOptions
::
FlagOptSeq
showtixOptions
=
showtixOptions
=
...
@@ -42,35 +59,46 @@ showtixMain flags (prog : modNames) = do
...
@@ -42,35 +59,46 @@ showtixMain flags (prog : modNames) = do
Nothing
->
Nothing
->
hpcError
showtixPlugin
$
"could not read .tix file : "
++
prog
hpcError
showtixPlugin
$
"could not read .tix file : "
++
prog
Just
(
Tix
tixs
)
->
do
Just
(
Tix
tixs
)
->
do
tixs_mixs
<-
-- Filter out TixModule's we are not interested in.
sequence
let
tixs_filtered
=
filter
(
allowModule
hpcflags1
.
tixModuleName
)
tixs
[
do
-- Read the corresponding Mix file for each TixModule
mix
<-
readMixWithFlags
hpcflags1
(
Right
tix
)
tixs_mixs
<-
forM
tixs_filtered
$
\
tix
->
do
return
(
tix
,
mix
)
mix
<-
readMixWithFlags
hpcflags1
(
Right
tix
)
|
tix
<-
tixs
,
pure
(
tix
,
mix
)
allowModule
hpcflags1
(
tixModuleName
tix
)
]
forM_
tixs_mixs
printTixModule
printTixModule
::
-- | A TixModule and the corresponding Mix-file
(
TixModule
,
Mix
)
->
IO
()
printTixModule
(
TixModule
modName
_
_
tixs
,
Mix
_
_
_
_
entries
)
=
do
let
enumerated
::
[(
Int
,
Integer
,
MixEntry
)]
enumerated
=
zip3
[(
0
::
Int
)
..
]
tixs
entries
forM_
enumerated
$
\
(
ix
,
count
,
(
pos
,
lab
))
->
do
putStrLn
(
rjust
5
(
show
ix
)
++
" "
++
rjust
10
(
show
count
)
++
" "
++
ljust
20
modName
++
" "
++
rjust
20
(
show
pos
)
++
" "
++
show
lab
)
let
rjust
n
str
=
replicate
(
n
-
length
str
)
' '
++
str
-- | Pad input with space on the left.
let
ljust
n
str
=
str
++
replicate
(
n
-
length
str
)
' '
--
-- >>> rjust 10 "hi"
-- " hi"
rjust
::
Int
->
String
->
String
rjust
n
str
=
replicate
(
n
-
length
str
)
' '
++
str
sequence_
-- | Pad input with space on the right.
[
sequence_
--
[
putStrLn
-- >>> ljust 10 "hi"
(
rjust
5
(
show
ix
)
-- "hi "
++
" "
ljust
::
Int
->
String
->
String
++
rjust
10
(
show
count
)
ljust
n
str
=
str
++
replicate
(
n
-
length
str
)
' '
++
" "
++
ljust
20
modName
++
" "
++
rjust
20
(
show
pos
)
++
" "
++
show
lab
)
|
(
count
,
ix
,
(
pos
,
lab
))
<-
zip3
tixs'
[(
0
::
Int
)
..
]
entries
]
|
(
TixModule
modName
_hash1
_
tixs'
,
Mix
_file
_timestamp
_hash2
_tab
entries
)
<-
tixs_mixs
]
This diff is collapsed.
Click to expand it.
Preview
0%
Loading
Try again
or
attach a new file
.
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Save comment
Cancel
Please
register
or
sign in
to comment