xref: /OpenGrok/opengrok-indexer/src/main/jflex/analysis/erlang/ErlangXref.lex (revision d219b4cea555a12b602d2d5518daa22134ad4879)
1 /*
2  * CDDL HEADER START
3  *
4  * The contents of this file are subject to the terms of the
5  * Common Development and Distribution License (the "License").
6  * You may not use this file except in compliance with the License.
7  *
8  * See LICENSE.txt included in this distribution for the specific
9  * language governing permissions and limitations under the License.
10  *
11  * When distributing Covered Code, include this CDDL HEADER in each
12  * file and include the License file at LICENSE.txt.
13  * If applicable, add the following below this CDDL HEADER, with the
14  * fields enclosed by brackets "[]" replaced with your own identifying
15  * information: Portions Copyright [yyyy] [name of copyright owner]
16  *
17  * CDDL HEADER END
18  */
19 
20 /*
21  * Copyright (c) 2015, 2021, Oracle and/or its affiliates. All rights reserved.
22  * Portions Copyright (c) 2017, Chris Fraire <cfraire@me.com>.
23  */
24 
25 /*
26  * Cross reference an Erlang file
27  */
28 
29 package org.opengrok.indexer.analysis.erlang;
30 
31 import java.io.IOException;
32 import org.opengrok.indexer.analysis.JFlexSymbolMatcher;
33 import org.opengrok.indexer.util.StringUtils;
34 import org.opengrok.indexer.web.HtmlConsts;
35 %%
36 %public
37 %class ErlangXref
38 %extends JFlexSymbolMatcher
39 %unicode
40 %int
41 %char
42 %include ../CommonLexer.lexh
43 %include ../CommonXref.lexh
44 %{
45     @Override
yypop()46     public void yypop() throws IOException {
47         onDisjointSpanChanged(null, yychar);
48         super.yypop();
49     }
50 
chkLOC()51     protected void chkLOC() {
52         switch (yystate()) {
53             case COMMENT:
54                 break;
55             default:
56                 phLOC();
57                 break;
58         }
59     }
60 %}
61 
62 IncludeDirective = (include|include_lib)
63 
64 File = [a-zA-Z]{FNameChar}* "." ([Ee][Rr][Ll] | [Hh][Rr][Ll] | [Aa][Pp][Pp] |
65     [Aa][Ss][Nn] | [Yy][Rr][Ll] | [Aa][Ss][Nn][1] | [Xx][Mm][Ll] |
66     [Hh][Tt][Mm][Ll]?)
67 
68 %state  STRING COMMENT QATOM
69 
70 %include ../Common.lexh
71 %include ../CommonURI.lexh
72 %include ../CommonPath.lexh
73 %include Erlang.lexh
74 %%
75 <YYINITIAL>{
76 
77 "?" {Identifier} {  // Macros
78     chkLOC();
79     onDisjointSpanChanged(HtmlConsts.MACRO_CLASS, yychar);
80     onNonSymbolMatched(yytext(), yychar);
81     onDisjointSpanChanged(null, yychar);
82 }
83 
84 {Identifier} {
85     chkLOC();
86     String id = yytext();
87     if (!id.equals("_")) {
88         onFilteredSymbolMatched(id, yychar, Consts.kwd);
89     } else {
90         onNonSymbolMatched(id, yychar);
91     }
92 }
93 
94 "-" {IncludeDirective} "(" ({File}|{FPath}) ")." {
95         chkLOC();
96         String capture = yytext();
97         String parenth = capture.substring(capture.indexOf("("));
98         String opening = capture.substring(0, yylength() - parenth.length());
99         String lparen = parenth.substring(0, 1);
100         int rpos = parenth.indexOf(")");
101         String rparen = parenth.substring(rpos);
102         String path = parenth.substring(lparen.length(), rpos);
103 
104         onNonSymbolMatched(opening.substring(0, 1), yychar);
105         onSymbolMatched(opening.substring(1), yychar + 1);
106         onNonSymbolMatched(lparen, yychar + opening.length());
107         onFilelikeMatched(path, yychar + opening.length() + lparen.length());
108         onNonSymbolMatched(rparen, yychar + opening.length() +
109             lparen.length() + path.length());
110 }
111 
112 ^"-" {Identifier} {
113     chkLOC();
114     String capture = yytext();
115     String punc = capture.substring(0, 1);
116     String id = capture.substring(1);
117     onNonSymbolMatched(punc, yychar);
118     onFilteredSymbolMatched(id, yychar + punc.length(), Consts.modules_kwd);
119 }
120 
121 {ErlInt} |
122     {Number}    {
123     chkLOC();
124     onDisjointSpanChanged(HtmlConsts.NUMBER_CLASS, yychar);
125     onNonSymbolMatched(yytext(), yychar);
126     onDisjointSpanChanged(null, yychar + yylength());
127 }
128 
129  \"     {
130     chkLOC();
131     yypush(STRING);
132     onDisjointSpanChanged(HtmlConsts.STRING_CLASS, yychar);
133     onNonSymbolMatched(yytext(), yychar);
134  }
135 
136  \'     {
137     chkLOC();
138     yypush(QATOM);
139     onDisjointSpanChanged(HtmlConsts.STRING_CLASS, yychar);
140     onNonSymbolMatched(yytext(), yychar);
141  }
142 
143  "%"    {
144     yypush(COMMENT);
145     onDisjointSpanChanged(HtmlConsts.COMMENT_CLASS, yychar);
146     onNonSymbolMatched(yytext(), yychar);
147  }
148 }
149 
150 <STRING> {
151  \\[\"\\]    { chkLOC(); onNonSymbolMatched(yytext(), yychar); }
152  \"    {
153     chkLOC();
154     onNonSymbolMatched(yytext(), yychar);
155     yypop();
156  }
157 }
158 
159 <QATOM> {
160  \\[\'\\]    { chkLOC(); onNonSymbolMatched(yytext(), yychar); }
161  \'    {
162     chkLOC();
163     onNonSymbolMatched(yytext(), yychar);
164     yypop();
165  }
166 }
167 
168 <COMMENT> {
169   {ErlangWhspChar}*{EOL} {
170     yypop();
171     onEndOfLineMatched(yytext(), yychar);
172   }
173 }
174 
175 <YYINITIAL, STRING, COMMENT, QATOM> {
176 {ErlangWhspChar}*{EOL}    { onEndOfLineMatched(yytext(), yychar); }
177  \s     { onNonSymbolMatched(yytext(), yychar); }
178  [^]    { chkLOC(); onNonSymbolMatched(yytext(), yychar); }
179 }
180 
181 <STRING, COMMENT, QATOM> {
182  {FPath}    {
183      chkLOC();
184      onPathlikeMatched(yytext(), '/', false, yychar);
185  }
186 
187 {File}
188         {
189         chkLOC();
190         String path = yytext();
191         onFilelikeMatched(path, yychar);
192  }
193 
194 {FNameChar}+ "@" {FNameChar}+ "." {FNameChar}+
195         {
196           chkLOC();
197           onEmailAddressMatched(yytext(), yychar);
198         }
199 }
200 
201 <STRING, COMMENT> {
202     {BrowseableURI}    {
203         chkLOC();
204         onUriMatched(yytext(), yychar);
205     }
206 }
207 
208 <QATOM> {
209     {BrowseableURI}    {
210         chkLOC();
211         onUriMatched(yytext(), yychar, StringUtils.APOS_NO_BSESC);
212     }
213 }
214