@@ -95,198 +95,150 @@ let mergeTrieNodes (defaultChildSize: int) (tries: TrieNode array) =
9595
9696 root
9797
98- let rec mkTrieNodeFor ( file : FileWithAST ) : TrieNode =
99- let idx = file.Idx
100- let fileExposesToRoot = doesFileExposeContentToTheRoot file.AST
101-
102- match file.AST with
103- | ParsedInput.SigFile ( ParsedSigFileInput ( contents = contents)) ->
104- contents
105- |> List.choose
106- ( fun ( SynModuleOrNamespaceSig ( longId = longId ; kind = kind ; attribs = attribs ; decls = decls ; accessibility = _accessibility )) ->
107- let hasTypesOrAutoOpenNestedModules =
108- List.exists
109- ( function
110- | SynModuleSigDecl.Types _ -> true
111- | SynModuleSigDecl.NestedModule( moduleInfo = SynComponentInfo ( attributes = attributes)) ->
112- isAnyAttributeAutoOpen attributes
113- | _ -> false )
114- decls
115-
116- let isNamespace =
117- match kind with
118- | SynModuleOrNamespaceKind.AnonModule
119- | SynModuleOrNamespaceKind.NamedModule -> false
120- | SynModuleOrNamespaceKind.DeclaredNamespace
121- | SynModuleOrNamespaceKind.GlobalNamespace -> true
122-
123- let rootFiles = if fileExposesToRoot then hs idx else emptyHS ()
124-
125- let children =
126- let rec visit continuation ( xs : LongIdent ) =
127- match xs with
128- | [] -> failwith " should even empty"
129- | [ finalPart ] ->
130- let name = finalPart.idText
131-
132- let current =
133- if isNamespace then
134- TrieNodeInfo.Namespace(
135- name,
136- ( if hasTypesOrAutoOpenNestedModules then
137- hs idx
138- else
139- emptyHS ())
140- )
141- else
142- TrieNodeInfo.Module( name, idx)
143-
144- let children = List.choose ( mkTrieForNestedSigModule idx) decls
145-
146- continuation (
147- Dictionary<_, _>(
148- Seq.singleton (
149- KeyValuePair(
150- name,
151- {
152- Current = current
153- Children = Dictionary( children)
154- }
155- )
156- )
157- )
158- )
159- | head :: tail ->
160- let name = head.idText
161-
162- visit
163- ( fun node ->
164- let files =
165- match tail with
166- | [ _ ] ->
167- let topLevelModuleOrNamespaceHasAutoOpen = isAnyAttributeAutoOpen attribs
168-
169- if topLevelModuleOrNamespaceHasAutoOpen && not isNamespace then
170- hs idx
171- else
172- emptyHS ()
173- | _ -> emptyHS ()
174-
175- let current = TrieNodeInfo.Namespace( name, files)
176-
177- Dictionary<_, _>( Seq.singleton ( KeyValuePair( name, { Current = current; Children = node })))
178- |> continuation)
179- tail
180-
181- if List.isEmpty longId then
182- // This can happen for a namespace global.
183- // We collect the child nodes from the decls
184- List.choose ( mkTrieForNestedSigModule idx) decls |> Dictionary
98+ /// Process a top level SynModuleOrNamespace(Sig)
99+ let processSynModuleOrNamespace < 'Decl >
100+ ( mkTrieForDeclaration : int -> 'Decl -> KeyValuePair < string , TrieNode > option )
101+ ( idx : int )
102+ ( name : LongIdent )
103+ ( attributes : SynAttributes )
104+ ( kind : SynModuleOrNamespaceKind )
105+ ( hasTypesOrAutoOpenNestedModules : bool )
106+ ( decls : 'Decl list )
107+ : TrieNode =
108+ let isNamespace =
109+ match kind with
110+ | SynModuleOrNamespaceKind.AnonModule
111+ | SynModuleOrNamespaceKind.NamedModule -> false
112+ | SynModuleOrNamespaceKind.DeclaredNamespace
113+ | SynModuleOrNamespaceKind.GlobalNamespace -> true
114+
115+ let children =
116+ // Process the name of the ModuleOrNamespace.
117+ // For each part in the name a TrieNode shall be created.
118+ // Only the last node can be a module, depending on the SynModuleOrNamespaceKind.
119+ let rec visit continuation ( xs : LongIdent ) =
120+ match xs with
121+ | [] -> failwith " should not be empty"
122+ | [ finalPart ] ->
123+ let name = finalPart.idText
124+
125+ // A module always exposes the file index, as it could expose values and functions.
126+ // A namespace only exposes the file when it has types or nested modules with an [<AutoOpen>] attribute.
127+ // The reasoning is that a type could be inferred and a nested auto open module will lift its content one level up.
128+ let current =
129+ if isNamespace then
130+ TrieNodeInfo.Namespace(
131+ name,
132+ ( if hasTypesOrAutoOpenNestedModules then
133+ hs idx
134+ else
135+ emptyHS ())
136+ )
185137 else
186- visit id longId
187-
188- Some
189- {
190- Current = Root rootFiles
191- Children = children
192- })
193- |> List.toArray
194- |> mergeTrieNodes contents.Length
195- | ParsedInput.ImplFile ( ParsedImplFileInput ( contents = contents)) ->
196- contents
197- |> List.choose
198- ( fun ( SynModuleOrNamespace ( longId = longId ; attribs = attribs ; kind = kind ; decls = decls ; accessibility = _accessibility )) ->
199- let hasTypesOrAutoOpenNestedModules =
200- List.exists
201- ( function
202- | SynModuleDecl.Types _ -> true
203- | SynModuleDecl.NestedModule( moduleInfo = SynComponentInfo ( attributes = attributes)) ->
204- isAnyAttributeAutoOpen attributes
205- | _ -> false )
206- decls
207-
208- let isNamespace =
209- match kind with
210- | SynModuleOrNamespaceKind.AnonModule
211- | SynModuleOrNamespaceKind.NamedModule -> false
212- | SynModuleOrNamespaceKind.DeclaredNamespace
213- | SynModuleOrNamespaceKind.GlobalNamespace -> true
214-
215- let rootFiles = if fileExposesToRoot then hs idx else emptyHS ()
216-
217- let children =
218- let rec visit
219- ( continuation : Dictionary < ModuleSegment , TrieNode > -> Dictionary < ModuleSegment , TrieNode >)
220- ( xs : LongIdent )
221- : Dictionary < ModuleSegment , TrieNode > =
222- match xs with
223- | [] -> failwith " should even empty"
224- | [ finalPart ] ->
225- let name = finalPart.idText
226-
227- let current =
228- if isNamespace then
229- TrieNodeInfo.Namespace(
230- name,
231- ( if hasTypesOrAutoOpenNestedModules then
232- hs idx
233- else
234- emptyHS ())
235- )
236- else
237- TrieNodeInfo.Module( name, idx)
238-
239- let children = List.choose ( mkTrieForSynModuleDecl idx) decls
240-
241- continuation (
242- Dictionary<_, _>(
243- Seq.singleton (
244- KeyValuePair(
245- name,
246- {
247- Current = current
248- Children = Dictionary( children)
249- }
250- )
251- )
252- )
138+ TrieNodeInfo.Module( name, idx)
139+
140+ let children = List.choose ( mkTrieForDeclaration idx) decls
141+
142+ continuation (
143+ Dictionary<_, _>(
144+ Seq.singleton (
145+ KeyValuePair(
146+ name,
147+ {
148+ Current = current
149+ Children = Dictionary( children)
150+ }
253151 )
254- | head :: tail ->
255- let name = head.idText
256-
257- visit
258- ( fun node ->
259- let files =
260- match tail with
261- | [ _ ] ->
262- let topLevelModuleOrNamespaceHasAutoOpen = isAnyAttributeAutoOpen attribs
263-
264- if topLevelModuleOrNamespaceHasAutoOpen && not isNamespace then
265- hs idx
266- else
267- emptyHS ()
268- | _ -> emptyHS ()
269-
270- let current = TrieNodeInfo.Namespace( name, files)
271-
272- Dictionary<_, _>( Seq.singleton ( KeyValuePair( name, { Current = current; Children = node })))
273- |> continuation)
274- tail
275-
276- if List.isEmpty longId then
277- // This can happen for anonymous modules and namespace global.
278- // We collect the child nodes from the decls
279- List.choose ( mkTrieForSynModuleDecl idx) decls |> Dictionary
280- else
281- visit id longId
152+ )
153+ )
154+ )
155+ | head :: tail ->
156+ let name = head.idText
157+
158+ visit
159+ ( fun node ->
160+ let files =
161+ match tail with
162+ | [ _ ] ->
163+ // In case you have:
164+ // [<AutoOpen>]
165+ // module A.B
166+ //
167+ // We should consider the namespace A to expose the current file.
168+ // Due to the [<AutoOpen>] we treat A the same way we would module B.
169+ let topLevelModuleOrNamespaceHasAutoOpen = isAnyAttributeAutoOpen attributes
170+
171+ if topLevelModuleOrNamespaceHasAutoOpen && not isNamespace then
172+ hs idx
173+ else
174+ emptyHS ()
175+ | _ -> emptyHS ()
282176
283- Some
284- {
285- Current = Root rootFiles
286- Children = children
287- })
288- |> List.toArray
289- |> mergeTrieNodes contents.Length
177+ let current = TrieNodeInfo.Namespace( name, files)
178+
179+ Dictionary<_, _>( Seq.singleton ( KeyValuePair( name, { Current = current; Children = node })))
180+ |> continuation)
181+ tail
182+
183+ if List.isEmpty name then
184+ // This can happen for a namespace global.
185+ // We collect the child nodes from the decls
186+ List.choose ( mkTrieForDeclaration idx) decls |> Dictionary
187+ else
188+ visit id name
189+
190+ {
191+ Current = Root( emptyHS ())
192+ Children = children
193+ }
194+
195+ let rec mkTrieNodeFor ( file : FileWithAST ) : TrieNode =
196+ let idx = file.Idx
197+
198+ if doesFileExposeContentToTheRoot file.AST then
199+ // If a file exposes content which does not need an open statement to access, we consider the file to be part of the root.
200+ {
201+ Current = Root( hs idx)
202+ Children = Dictionary( 0 )
203+ }
204+ else
205+ match file.AST with
206+ | ParsedInput.SigFile ( ParsedSigFileInput ( contents = contents)) ->
207+ contents
208+ |> List.map
209+ ( fun ( SynModuleOrNamespaceSig ( longId = longId
210+ kind = kind
211+ attribs = attribs
212+ decls = decls
213+ accessibility = _accessibility )) ->
214+ let hasTypesOrAutoOpenNestedModules =
215+ List.exists
216+ ( function
217+ | SynModuleSigDecl.Types _ -> true
218+ | SynModuleSigDecl.NestedModule( moduleInfo = SynComponentInfo ( attributes = attributes)) ->
219+ isAnyAttributeAutoOpen attributes
220+ | _ -> false )
221+ decls
222+
223+ processSynModuleOrNamespace mkTrieForSynModuleSigDecl idx longId attribs kind hasTypesOrAutoOpenNestedModules decls)
224+ |> List.toArray
225+ |> mergeTrieNodes contents.Length
226+ | ParsedInput.ImplFile ( ParsedImplFileInput ( contents = contents)) ->
227+ contents
228+ |> List.map
229+ ( fun ( SynModuleOrNamespace ( longId = longId ; attribs = attribs ; kind = kind ; decls = decls ; accessibility = _accessibility )) ->
230+ let hasTypesOrAutoOpenNestedModules =
231+ List.exists
232+ ( function
233+ | SynModuleDecl.Types _ -> true
234+ | SynModuleDecl.NestedModule( moduleInfo = SynComponentInfo ( attributes = attributes)) ->
235+ isAnyAttributeAutoOpen attributes
236+ | _ -> false )
237+ decls
238+
239+ processSynModuleOrNamespace mkTrieForSynModuleDecl idx longId attribs kind hasTypesOrAutoOpenNestedModules decls)
240+ |> List.toArray
241+ |> mergeTrieNodes contents.Length
290242
291243and mkTrieForSynModuleDecl ( fileIndex : int ) ( decl : SynModuleDecl ) : KeyValuePair < string , TrieNode > option =
292244 match decl with
@@ -305,11 +257,11 @@ and mkTrieForSynModuleDecl (fileIndex: int) (decl: SynModuleDecl) : KeyValuePair
305257 )
306258 | _ -> None
307259
308- and mkTrieForNestedSigModule ( fileIndex : int ) ( decl : SynModuleSigDecl ) : KeyValuePair < string , TrieNode > option =
260+ and mkTrieForSynModuleSigDecl ( fileIndex : int ) ( decl : SynModuleSigDecl ) : KeyValuePair < string , TrieNode > option =
309261 match decl with
310262 | SynModuleSigDecl.NestedModule ( moduleInfo = SynComponentInfo( longId = [ nestedModuleIdent ]); moduleDecls = decls) ->
311263 let name = nestedModuleIdent.idText
312- let children = List.choose ( mkTrieForNestedSigModule fileIndex) decls
264+ let children = List.choose ( mkTrieForSynModuleSigDecl fileIndex) decls
313265
314266 Some(
315267 KeyValuePair(
0 commit comments