From dff9b40fe9f565bfb4be95c2e9f404c53ce69c9f Mon Sep 17 00:00:00 2001 From: Jakob C Date: Mon, 25 Feb 2013 15:04:45 +0100 Subject: [PATCH] Fix of failing tests (completion) --- .../src/org/erlide/model/util/ModelUtils.java | 803 +++++++++--------- .../erlide/ui/tests/ContentAssistTest.java | 7 +- .../AbstractErlContentAssistProcessor.java | 6 +- 3 files changed, 410 insertions(+), 406 deletions(-) diff --git a/org.erlide.model.api/src/org/erlide/model/util/ModelUtils.java b/org.erlide.model.api/src/org/erlide/model/util/ModelUtils.java index 00cb7c2acf..d8b9f7c6f4 100644 --- a/org.erlide.model.api/src/org/erlide/model/util/ModelUtils.java +++ b/org.erlide.model.api/src/org/erlide/model/util/ModelUtils.java @@ -20,11 +20,11 @@ import org.erlide.model.erlang.IErlPreprocessorDef; import org.erlide.model.erlang.IErlTypespec; import org.erlide.model.root.IErlElement; +import org.erlide.model.root.IErlElement.Kind; import org.erlide.model.root.IErlElementLocator; import org.erlide.model.root.IErlExternal; import org.erlide.model.root.IErlModel; import org.erlide.model.root.IErlProject; -import org.erlide.model.root.IErlElement.Kind; import org.erlide.utils.ErlLogger; import org.erlide.utils.StringUtils; @@ -39,404 +39,407 @@ public class ModelUtils { - private static final String DELIMITER = "<>"; - - public static IErlTypespec findTypespec(final IErlModule module, - final String name) throws CoreException { - IErlTypespec typespec = module.findTypespec(name); - if (typespec != null) { - return typespec; - } - final Collection includedFiles = module - .findAllIncludedFiles(); - for (final IErlModule includedFile : includedFiles) { - typespec = includedFile.findTypespec(name); - if (typespec != null) { - return typespec; - } - } - return null; - } - - public static String getExternalModulePath(final IErlElementLocator model, - final IErlModule module) { - final List result = Lists.newArrayList(); - IErlElement element = module; - while (element != model) { - if (element instanceof IErlExternal) { - final IErlExternal external = (IErlExternal) element; - result.add(external.getName()); - } else { - result.add(element.getName()); - } - element = (IErlElement) element.getParent(); - } - return Joiner.on(DELIMITER).join(Lists.reverse(result)); - } - - private static IErlExternal getElementWithExternalName( - final IParent parent, final String segment) - throws ErlModelException { - for (final IErlElement i : parent.getChildrenOfKind(Kind.EXTERNAL)) { - final IErlExternal external = (IErlExternal) i; - final String externalName = external.getName(); - ErlLogger - .debug("externalName %s segment %s", externalName, segment); - if (externalName.equals(segment)) { - return external; - } - } - return null; - } - - public static IErlModule getModuleFromExternalModulePath( - final IErlModel model, final String modulePath) - throws ErlModelException { - final List path = Lists.newArrayList(Splitter.on(DELIMITER) - .split(modulePath)); - model.open(null); - final IErlElement childNamed = model.getChildNamed(path.get(0)); - ErlLogger.debug(">>childNamed %s", childNamed == null ? "" - : childNamed.getName()); - if (childNamed instanceof IParent) { - IParent parent = (IParent) childNamed; - final int n = path.size() - 1; - for (int i = 1;; i++) { - if (parent == null) { - break; - } - if (parent instanceof IOpenable) { - final IOpenable openable = (IOpenable) parent; - openable.open(null); - } - if (i == n) { - break; - } - parent = getElementWithExternalName(parent, path.get(i)); - ErlLogger.debug(">>parent %s", parent); - } - if (parent != null) { - final IErlElement child = parent.getChildNamed(path.get(n)); - if (child instanceof IErlModule) { - return (IErlModule) child; - } - } - } - return null; - } - - public static List findUnitsWithPrefix(final String prefix, - final IErlProject project, final boolean checkExternals, - final boolean includes) throws ErlModelException { - final List result = Lists.newArrayList(); - final Set names = Sets.newHashSet(); - final Collection units = getUnits(project, checkExternals, - includes); - addUnitNamesWithPrefix(prefix, result, names, units, false, includes); - for (final IErlProject p : project.getReferencedProjects()) { - if (p != null) { - p.open(null); - addUnitNamesWithPrefix(prefix, result, names, - getUnits(p, checkExternals, includes), false, includes); - } - } - if (checkExternals) { - final Collection externalUnits = includes ? project - .getExternalIncludes() : project.getExternalModules(); - addUnitNamesWithPrefix(prefix, result, names, externalUnits, true, - includes); - } - return result; - } - - private static Collection getUnits(final IErlProject project, - final boolean checkExternals, final boolean includes) - throws ErlModelException { - final Collection units; - if (!includes) { - units = project.getModules(); - } else if (!checkExternals) { - units = project.getIncludes(); - } else { - units = Sets.newHashSet(); - } - return units; - } - - public static String resolveMacroValue(final String definedName, - final IErlModule module) { - if (module != null) { - if ("?MODULE".equals(definedName)) { - return module.getModuleName(); - } - final IErlPreprocessorDef def = module.findPreprocessorDef( - StringUtils.withoutInterrogationMark(definedName), - Kind.MACRO_DEF); - if (def != null) { - final String extra = def.getExtra(); - final int p = extra.indexOf(','); - if (p != -1) { - final String s = extra.substring(p + 1).trim(); - if (s.length() > 0) { - return s; - } - } - } - } - return definedName; - } - - public static IErlFunction findFunction(final IErlElementLocator model, - String moduleName, final ErlangFunction erlangFunction, - final String modulePath, final IErlProject project, - final IErlElementLocator.Scope scope, final IErlModule module) - throws CoreException { - if (moduleName != null) { - moduleName = resolveMacroValue(moduleName, module); - final IErlModule module2 = findModule(model, project, moduleName, - modulePath, scope); - if (module2 != null) { - module2.open(null); - final IErlFunction function = module2 - .findFunction(erlangFunction); - if (function != null) { - return function; - } - return null; - } - } - return null; - } - - public static IErlModule findModule(final IErlElementLocator model, - final IErlProject project, final String moduleName, - final String modulePath, final IErlElementLocator.Scope scope) - throws ErlModelException { - if (project != null) { - return model.findModuleFromProject(project, moduleName, modulePath, - scope); - } - if (scope == IErlElementLocator.Scope.ALL_PROJECTS) { - return model.findModule(moduleName, modulePath); - } - return null; - } - - public static IErlElement findTypeDef(final IErlElementLocator model, - final IErlModule module, String moduleName, final String typeName, - final String modulePath, final IErlProject project, - final IErlElementLocator.Scope scope) throws CoreException { - moduleName = resolveMacroValue(moduleName, module); - final IErlModule module2 = findModule(model, project, moduleName, - modulePath, scope); - if (module2 != null) { - module2.open(null); - return module2.findTypespec(typeName); - } - return null; - } - - public static IErlPreprocessorDef findPreprocessorDef( - final Collection projects, final String moduleName, - final String definedName, final IErlElement.Kind kind) - throws CoreException { - for (final IErlProject project : projects) { - if (project != null) { - final IErlModule module = project.getModule(moduleName); - if (module != null) { - final IErlPreprocessorDef def = findPreprocessorDef(module, - definedName, kind); - if (def != null) { - return def; - } - } - } - } - return null; - } - - public static IErlPreprocessorDef findPreprocessorDef( - final IErlModule module, final String definedName, - final IErlElement.Kind kind) throws CoreException { - String unquoted = StringUtils.unquote(definedName); - final String quoted = StringUtils.quote(definedName); - final Set names = new HashSet(3); - if (kind == Kind.RECORD_DEF) { - while (names.add(unquoted)) { - unquoted = resolveMacroValue(unquoted, module); - } - } else { - names.add(unquoted); - } - names.add(quoted); - names.add(definedName); - final List allIncludedFiles = Lists.newArrayList(module - .findAllIncludedFiles()); - allIncludedFiles.add(0, module); - for (final IErlModule includedFile : allIncludedFiles) { - for (final String name : names) { - includedFile.open(null); - final IErlPreprocessorDef preprocessorDef = includedFile - .findPreprocessorDef(name, kind); - if (preprocessorDef != null) { - return preprocessorDef; - } - } - } - return null; - } - - public static List getImportsAsList(final IErlModule mod) { - if (mod == null) { - return NO_IMPORTS; - } - final Collection imports = mod.getImports(); - if (imports.isEmpty()) { - return NO_IMPORTS; - } - final List result = new ArrayList( - imports.size()); - for (final IErlImport i : imports) { - final Collection functions = i.getFunctions(); - final OtpErlangObject funsT[] = new OtpErlangObject[functions - .size()]; - int j = 0; - for (final ErlangFunction f : functions) { - funsT[j] = f.getNameArityTuple(); - j++; - } - final OtpErlangTuple modFunsT = new OtpErlangTuple( - new OtpErlangObject[] { - new OtpErlangAtom(i.getImportModule()), - new OtpErlangList(funsT) }); - result.add(modFunsT); - } - return result; - } - - public static List getAllPreprocessorDefs( - final IErlModule module, final IErlElement.Kind kind) - throws CoreException { - final List result = Lists.newArrayList(); - final List modulesWithIncludes = Lists.newArrayList(module - .findAllIncludedFiles()); - modulesWithIncludes.add(module); - for (final IErlModule m : modulesWithIncludes) { - result.addAll(m.getPreprocessorDefs(kind)); - } - return result; - } - - public static final ArrayList NO_IMPORTS = new ArrayList( - 0); - - private static void addUnitNamesWithPrefix(final String prefix, - final List result, final Set names, - final Collection modules, final boolean external, - final boolean includes) { - for (final IErlModule module : modules) { - String moduleName = includes ? module.getName() : module - .getModuleName(); - if (external && includes) { - moduleName = getIncludeLibPath(module); - } - if (moduleName.startsWith(prefix)) { - if (!names.contains(moduleName)) { - result.add(moduleName); - names.add(moduleName); - } - } - } - } - - private static String getIncludeLibPath(final IErlModule module) { - String s = module.getName(); - String prevS = s; - IErlElement e = module; - for (;;) { - final IParent p = e.getParent(); - if (p instanceof IErlProject) { - break; - } - e = (IErlElement) p; - prevS = s; - s = e.getName() + "/" + s; - } - return prevS; - } - - public static String[] getPredefinedMacroNames() { - return new String[] { "MODULE", "LINE", "FILE" }; - } - - public static boolean isOtpModule(final IErlModule module) { - IParent parent = module.getParent(); - while (parent instanceof IErlExternal) { - final IErlExternal external = (IErlExternal) parent; - if (external.isOTP()) { - return true; - } - parent = external.getParent(); - } - return false; - } - - public static IErlModule getModule(final IErlElement element) { - if (element instanceof IErlModule) { - return (IErlModule) element; - } - return (IErlModule) element.getAncestorOfKind(Kind.MODULE); - } - - public static IErlProject getProject(final IErlElement element) { - final IErlElement ancestor = element.getAncestorOfKind(Kind.PROJECT); - if (ancestor instanceof IErlProject) { - return (IErlProject) ancestor; - } - return null; - } - - /** - * Helper method - returns the targeted item (IResource if internal or - * java.io.File if external), or null if unbound Internal items must be - * referred to using container relative paths. - */ - public static Object getTarget(final IContainer container, - final IPath path, final boolean checkResourceExistence) { - - if (path == null) { - return null; - } - - // lookup - inside the container - if (path.getDevice() == null) { // container relative paths should not - // contain a device - // (see http://dev.eclipse.org/bugs/show_bug.cgi?id=18684) - // (case of a workspace rooted at d:\ ) - final IResource resource = container.findMember(path); - if (resource != null) { - if (!checkResourceExistence || resource.exists()) { - return resource; - } - return null; - } - } - - // if path is relative, it cannot be an external path - // (see http://dev.eclipse.org/bugs/show_bug.cgi?id=22517) - if (!path.isAbsolute()) { - return null; - } - - // lookup - outside the container - final File externalFile = new File(path.toOSString()); - if (!checkResourceExistence) { - return externalFile; - } - if (externalFile.exists()) { - return externalFile; - } - return null; - } + private static final String DELIMITER = "<>"; + + public static IErlTypespec findTypespec(final IErlModule module, + final String name) throws CoreException { + IErlTypespec typespec = module.findTypespec(name); + if (typespec != null) { + return typespec; + } + final Collection includedFiles = module + .findAllIncludedFiles(); + for (final IErlModule includedFile : includedFiles) { + typespec = includedFile.findTypespec(name); + if (typespec != null) { + return typespec; + } + } + return null; + } + + public static String getExternalModulePath(final IErlElementLocator model, + final IErlModule module) { + final List result = Lists.newArrayList(); + IErlElement element = module; + while (element != model) { + if (element instanceof IErlExternal) { + final IErlExternal external = (IErlExternal) element; + result.add(external.getName()); + } else { + result.add(element.getName()); + } + element = (IErlElement) element.getParent(); + } + return Joiner.on(DELIMITER).join(Lists.reverse(result)); + } + + private static IErlExternal getElementWithExternalName( + final IParent parent, final String segment) + throws ErlModelException { + for (final IErlElement i : parent.getChildrenOfKind(Kind.EXTERNAL)) { + final IErlExternal external = (IErlExternal) i; + final String externalName = external.getName(); + ErlLogger + .debug("externalName %s segment %s", externalName, segment); + if (externalName.equals(segment)) { + return external; + } + } + return null; + } + + public static IErlModule getModuleFromExternalModulePath( + final IErlModel model, final String modulePath) + throws ErlModelException { + final List path = Lists.newArrayList(Splitter.on(DELIMITER) + .split(modulePath)); + model.open(null); + final IErlElement childNamed = model.getChildNamed(path.get(0)); + ErlLogger.debug(">>childNamed %s", childNamed == null ? "" + : childNamed.getName()); + if (childNamed instanceof IParent) { + IParent parent = (IParent) childNamed; + final int n = path.size() - 1; + for (int i = 1;; i++) { + if (parent == null) { + break; + } + if (parent instanceof IOpenable) { + final IOpenable openable = (IOpenable) parent; + openable.open(null); + } + if (i == n) { + break; + } + parent = getElementWithExternalName(parent, path.get(i)); + ErlLogger.debug(">>parent %s", parent); + } + if (parent != null) { + final IErlElement child = parent.getChildNamed(path.get(n)); + if (child instanceof IErlModule) { + return (IErlModule) child; + } + } + } + return null; + } + + public static List findUnitsWithPrefix(final String prefix, + final IErlProject project, final boolean checkExternals, + final boolean includes) throws ErlModelException { + final List result = Lists.newArrayList(); + final Set names = Sets.newHashSet(); + final Collection units = getUnits(project, checkExternals, + includes); + addUnitNamesWithPrefix(prefix, result, names, units, false, includes); + if (project != null) { + for (final IErlProject p : project.getReferencedProjects()) { + if (p != null) { + p.open(null); + addUnitNamesWithPrefix(prefix, result, names, + getUnits(p, checkExternals, includes), false, + includes); + } + } + if (checkExternals) { + final Collection externalUnits = includes ? project + .getExternalIncludes() : project.getExternalModules(); + addUnitNamesWithPrefix(prefix, result, names, externalUnits, + true, includes); + } + } + return result; + } + + private static Collection getUnits(final IErlProject project, + final boolean checkExternals, final boolean includes) + throws ErlModelException { + final Collection units; + if (!includes && project != null) { + units = project.getModules(); + } else if (!checkExternals && project != null) { + units = project.getIncludes(); + } else { + units = Sets.newHashSet(); + } + return units; + } + + public static String resolveMacroValue(final String definedName, + final IErlModule module) { + if (module != null) { + if ("?MODULE".equals(definedName)) { + return module.getModuleName(); + } + final IErlPreprocessorDef def = module.findPreprocessorDef( + StringUtils.withoutInterrogationMark(definedName), + Kind.MACRO_DEF); + if (def != null) { + final String extra = def.getExtra(); + final int p = extra.indexOf(','); + if (p != -1) { + final String s = extra.substring(p + 1).trim(); + if (s.length() > 0) { + return s; + } + } + } + } + return definedName; + } + + public static IErlFunction findFunction(final IErlElementLocator model, + String moduleName, final ErlangFunction erlangFunction, + final String modulePath, final IErlProject project, + final IErlElementLocator.Scope scope, final IErlModule module) + throws CoreException { + if (moduleName != null) { + moduleName = resolveMacroValue(moduleName, module); + final IErlModule module2 = findModule(model, project, moduleName, + modulePath, scope); + if (module2 != null) { + module2.open(null); + final IErlFunction function = module2 + .findFunction(erlangFunction); + if (function != null) { + return function; + } + return null; + } + } + return null; + } + + public static IErlModule findModule(final IErlElementLocator model, + final IErlProject project, final String moduleName, + final String modulePath, final IErlElementLocator.Scope scope) + throws ErlModelException { + if (project != null) { + return model.findModuleFromProject(project, moduleName, modulePath, + scope); + } + if (scope == IErlElementLocator.Scope.ALL_PROJECTS) { + return model.findModule(moduleName, modulePath); + } + return null; + } + + public static IErlElement findTypeDef(final IErlElementLocator model, + final IErlModule module, String moduleName, final String typeName, + final String modulePath, final IErlProject project, + final IErlElementLocator.Scope scope) throws CoreException { + moduleName = resolveMacroValue(moduleName, module); + final IErlModule module2 = findModule(model, project, moduleName, + modulePath, scope); + if (module2 != null) { + module2.open(null); + return module2.findTypespec(typeName); + } + return null; + } + + public static IErlPreprocessorDef findPreprocessorDef( + final Collection projects, final String moduleName, + final String definedName, final IErlElement.Kind kind) + throws CoreException { + for (final IErlProject project : projects) { + if (project != null) { + final IErlModule module = project.getModule(moduleName); + if (module != null) { + final IErlPreprocessorDef def = findPreprocessorDef(module, + definedName, kind); + if (def != null) { + return def; + } + } + } + } + return null; + } + + public static IErlPreprocessorDef findPreprocessorDef( + final IErlModule module, final String definedName, + final IErlElement.Kind kind) throws CoreException { + String unquoted = StringUtils.unquote(definedName); + final String quoted = StringUtils.quote(definedName); + final Set names = new HashSet(3); + if (kind == Kind.RECORD_DEF) { + while (names.add(unquoted)) { + unquoted = resolveMacroValue(unquoted, module); + } + } else { + names.add(unquoted); + } + names.add(quoted); + names.add(definedName); + final List allIncludedFiles = Lists.newArrayList(module + .findAllIncludedFiles()); + allIncludedFiles.add(0, module); + for (final IErlModule includedFile : allIncludedFiles) { + for (final String name : names) { + includedFile.open(null); + final IErlPreprocessorDef preprocessorDef = includedFile + .findPreprocessorDef(name, kind); + if (preprocessorDef != null) { + return preprocessorDef; + } + } + } + return null; + } + + public static List getImportsAsList(final IErlModule mod) { + if (mod == null) { + return NO_IMPORTS; + } + final Collection imports = mod.getImports(); + if (imports.isEmpty()) { + return NO_IMPORTS; + } + final List result = new ArrayList( + imports.size()); + for (final IErlImport i : imports) { + final Collection functions = i.getFunctions(); + final OtpErlangObject funsT[] = new OtpErlangObject[functions + .size()]; + int j = 0; + for (final ErlangFunction f : functions) { + funsT[j] = f.getNameArityTuple(); + j++; + } + final OtpErlangTuple modFunsT = new OtpErlangTuple( + new OtpErlangObject[] { + new OtpErlangAtom(i.getImportModule()), + new OtpErlangList(funsT) }); + result.add(modFunsT); + } + return result; + } + + public static List getAllPreprocessorDefs( + final IErlModule module, final IErlElement.Kind kind) + throws CoreException { + final List result = Lists.newArrayList(); + final List modulesWithIncludes = Lists.newArrayList(module + .findAllIncludedFiles()); + modulesWithIncludes.add(module); + for (final IErlModule m : modulesWithIncludes) { + result.addAll(m.getPreprocessorDefs(kind)); + } + return result; + } + + public static final ArrayList NO_IMPORTS = new ArrayList( + 0); + + private static void addUnitNamesWithPrefix(final String prefix, + final List result, final Set names, + final Collection modules, final boolean external, + final boolean includes) { + for (final IErlModule module : modules) { + String moduleName = includes ? module.getName() : module + .getModuleName(); + if (external && includes) { + moduleName = getIncludeLibPath(module); + } + if (moduleName.startsWith(prefix)) { + if (!names.contains(moduleName)) { + result.add(moduleName); + names.add(moduleName); + } + } + } + } + + private static String getIncludeLibPath(final IErlModule module) { + String s = module.getName(); + String prevS = s; + IErlElement e = module; + for (;;) { + final IParent p = e.getParent(); + if (p instanceof IErlProject) { + break; + } + e = (IErlElement) p; + prevS = s; + s = e.getName() + "/" + s; + } + return prevS; + } + + public static String[] getPredefinedMacroNames() { + return new String[] { "MODULE", "LINE", "FILE" }; + } + + public static boolean isOtpModule(final IErlModule module) { + IParent parent = module.getParent(); + while (parent instanceof IErlExternal) { + final IErlExternal external = (IErlExternal) parent; + if (external.isOTP()) { + return true; + } + parent = external.getParent(); + } + return false; + } + + public static IErlModule getModule(final IErlElement element) { + if (element instanceof IErlModule) { + return (IErlModule) element; + } + return (IErlModule) element.getAncestorOfKind(Kind.MODULE); + } + + public static IErlProject getProject(final IErlElement element) { + final IErlElement ancestor = element.getAncestorOfKind(Kind.PROJECT); + if (ancestor instanceof IErlProject) { + return (IErlProject) ancestor; + } + return null; + } + + /** + * Helper method - returns the targeted item (IResource if internal or + * java.io.File if external), or null if unbound Internal items must be + * referred to using container relative paths. + */ + public static Object getTarget(final IContainer container, + final IPath path, final boolean checkResourceExistence) { + + if (path == null) { + return null; + } + + // lookup - inside the container + if (path.getDevice() == null) { // container relative paths should not + // contain a device + // (see http://dev.eclipse.org/bugs/show_bug.cgi?id=18684) + // (case of a workspace rooted at d:\ ) + final IResource resource = container.findMember(path); + if (resource != null) { + if (!checkResourceExistence || resource.exists()) { + return resource; + } + return null; + } + } + + // if path is relative, it cannot be an external path + // (see http://dev.eclipse.org/bugs/show_bug.cgi?id=22517) + if (!path.isAbsolute()) { + return null; + } + + // lookup - outside the container + final File externalFile = new File(path.toOSString()); + if (!checkResourceExistence) { + return externalFile; + } + if (externalFile.exists()) { + return externalFile; + } + return null; + } } diff --git a/org.erlide.ui.tests/src/org/erlide/ui/tests/ContentAssistTest.java b/org.erlide.ui.tests/src/org/erlide/ui/tests/ContentAssistTest.java index e1c11e715a..a6e23fc60f 100644 --- a/org.erlide.ui.tests/src/org/erlide/ui/tests/ContentAssistTest.java +++ b/org.erlide.ui.tests/src/org/erlide/ui/tests/ContentAssistTest.java @@ -30,7 +30,6 @@ import org.eclipse.swt.custom.StyledText; import org.eclipse.swt.graphics.Color; import org.eclipse.swt.graphics.Point; -import org.erlide.model.ErlModelException; import org.erlide.model.erlang.IErlModule; import org.erlide.model.erlang.IErlScanner; import org.erlide.model.root.IErlProject; @@ -357,8 +356,8 @@ public void completionTestWithParsing(final IErlProject project, final MockSourceViewer sourceViewer = new MockSourceViewer(document, offset); final IContentAssistProcessor p = stringContentAssistProcessor ? new ErlStringContentAssistProcessor( - sourceViewer, module, null, null) - : new ErlContentAssistProcessor(sourceViewer, module, null, + sourceViewer, module, project, null) + : new ErlContentAssistProcessor(sourceViewer, module, project, null); final ICompletionProposal[] completionProposals = p .computeCompletionProposals(sourceViewer, offset); @@ -391,7 +390,7 @@ public void includeCompletionTest() throws Exception { private void completionTestWithoutParsing(final String initialText, final int nTotalExpectedCompletions, final String completionChar, final int nExpectedCompletions, final String expectedFirstCompletion) - throws ErlModelException { + throws CoreException { // http://www.assembla.com/spaces/erlide/tickets/593-completion--don-t-work-records-with-quoted-names- final int offset = initialText.length(); IDocument document = new StringDocument(initialText); diff --git a/org.erlide.ui/src/org/erlide/ui/editors/erl/completion/AbstractErlContentAssistProcessor.java b/org.erlide.ui/src/org/erlide/ui/editors/erl/completion/AbstractErlContentAssistProcessor.java index 0a3c1db321..45176bca75 100644 --- a/org.erlide.ui/src/org/erlide/ui/editors/erl/completion/AbstractErlContentAssistProcessor.java +++ b/org.erlide.ui/src/org/erlide/ui/editors/erl/completion/AbstractErlContentAssistProcessor.java @@ -33,9 +33,9 @@ import org.erlide.model.erlang.ISourceReference; import org.erlide.model.root.ErlModelManager; import org.erlide.model.root.IErlElement; +import org.erlide.model.root.IErlElement.Kind; import org.erlide.model.root.IErlElementLocator; import org.erlide.model.root.IErlProject; -import org.erlide.model.root.IErlElement.Kind; import org.erlide.model.services.codeassist.ErlideContextAssist; import org.erlide.model.services.codeassist.ErlideContextAssist.RecordCompletion; import org.erlide.model.services.search.ErlideDoc; @@ -286,8 +286,10 @@ private List addCompletions(final Set flags, final int offset, final String prefix, final String moduleOrRecord, final int pos, final List fieldsSoFar) throws CoreException, OtpErlangRangeException, BadLocationException { + final IProject workspaceProject = project != null ? project + .getWorkspaceProject() : null; final IRpcSite backend = BackendCore.getBuildOrIdeBackend( - project.getWorkspaceProject()).getRpcSite(); + workspaceProject).getRpcSite(); final List result = new ArrayList(); if (flags.contains(Kinds.DECLARED_FUNCTIONS)) { addSorted(