diff --git a/docs/release-notes/.FSharp.Compiler.Service/11.0.0.md b/docs/release-notes/.FSharp.Compiler.Service/11.0.0.md index 655ad02ad2..4dde23380c 100644 --- a/docs/release-notes/.FSharp.Compiler.Service/11.0.0.md +++ b/docs/release-notes/.FSharp.Compiler.Service/11.0.0.md @@ -9,6 +9,8 @@ ### Added +* #ELIF preprocessor directive ([PR #19045](https://github.com/dotnet/fsharp/pull/19045)) + ### Changed * Parallel compilation stabilised and enabled by default ([PR #18998](https://github.com/dotnet/fsharp/pull/18998)) diff --git a/src/Compiler/Service/ServiceLexing.fs b/src/Compiler/Service/ServiceLexing.fs index 74141b4805..87c0e79db5 100644 --- a/src/Compiler/Service/ServiceLexing.fs +++ b/src/Compiler/Service/ServiceLexing.fs @@ -408,6 +408,7 @@ module internal TokenClassifications = | HASH_LINE _ | WARN_DIRECTIVE _ | HASH_IF _ + | HASH_ELIF _ | HASH_ELSE _ | HASH_ENDIF _ -> (FSharpTokenColorKind.PreprocessorKeyword, FSharpTokenCharKind.WhiteSpace, FSharpTokenTriggerClass.None) @@ -486,6 +487,7 @@ module internal LexerStateEncoding = | HASH_LINE cont | HASH_LIGHT cont | HASH_IF(_, _, cont) + | HASH_ELIF(_, _, cont) | HASH_ELSE(_, _, cont) | HASH_ENDIF(_, _, cont) | INACTIVECODE cont @@ -613,6 +615,7 @@ module internal LexerStateEncoding = match ifOrElse with | IfDefIf, _ -> () | IfDefElse, _ -> ifdefStackBits <- (ifdefStackBits ||| (1 <<< ifdefStackCount)) + | IfDefSkipRemaining, _ -> ifdefStackBits <- (ifdefStackBits ||| (1 <<< ifdefStackCount)) ifdefStackCount <- ifdefStackCount + 1 @@ -1051,6 +1054,7 @@ type FSharpLineTokenizer(lexbuf: UnicodeLexing.Lexbuf, maxLength: int option, fi // for VS (which needs to recognize when user types "."). match token with | HASH_IF(m, lineStr, cont) when lineStr <> "" -> false, processHashIfLine m.StartColumn lineStr cont + | HASH_ELIF(m, lineStr, cont) when lineStr <> "" -> false, processHashIfLine m.StartColumn lineStr cont | HASH_ELSE(m, lineStr, cont) when lineStr <> "" -> false, processHashEndElse m.StartColumn lineStr 4 cont | HASH_ENDIF(m, lineStr, cont) when lineStr <> "" -> false, processHashEndElse m.StartColumn lineStr 5 cont | WARN_DIRECTIVE(_, s, cont) -> false, processWarnDirective s leftc rightc cont @@ -1301,6 +1305,7 @@ type FSharpLexerFlags = type FSharpTokenKind = | None | HashIf + | HashElif | HashElse | HashEndIf | WarnDirective @@ -1515,6 +1520,7 @@ type FSharpToken = | INFIX_STAR_DIV_MOD_OP "lxor" -> FSharpTokenKind.InfixLxor | INFIX_STAR_DIV_MOD_OP "mod" -> FSharpTokenKind.InfixMod | HASH_IF _ -> FSharpTokenKind.HashIf + | HASH_ELIF _ -> FSharpTokenKind.HashElif | HASH_ELSE _ -> FSharpTokenKind.HashElse | HASH_ENDIF _ -> FSharpTokenKind.HashEndIf | WARN_DIRECTIVE _ -> FSharpTokenKind.WarnDirective diff --git a/src/Compiler/Service/ServiceLexing.fsi b/src/Compiler/Service/ServiceLexing.fsi index 869b295d33..32c2256317 100755 --- a/src/Compiler/Service/ServiceLexing.fsi +++ b/src/Compiler/Service/ServiceLexing.fsi @@ -369,6 +369,7 @@ type public FSharpLexerFlags = type public FSharpTokenKind = | None | HashIf + | HashElif | HashElse | HashEndIf | WarnDirective diff --git a/src/Compiler/Service/ServiceStructure.fs b/src/Compiler/Service/ServiceStructure.fs index bcf0d8d2bc..859e9213e7 100644 --- a/src/Compiler/Service/ServiceStructure.fs +++ b/src/Compiler/Service/ServiceStructure.fs @@ -717,13 +717,39 @@ module Structure = match directives with | [] -> () | ConditionalDirectiveTrivia.If _ as ifDirective :: directives -> group directives (ifDirective :: stack) sourceLines + | ConditionalDirectiveTrivia.Elif(_, elifRange) as elifDirective :: directives -> + match stack with + | ConditionalDirectiveTrivia.If(_, ifRange) :: stack + | ConditionalDirectiveTrivia.Elif(_, ifRange) :: stack -> + let startLineIndex = elifRange.StartLine - 2 + + if startLineIndex >= 0 then + // start of #if (or previous #elif) until the end of the line directly above current #elif + + let range = + mkFileIndexRange + ifRange.FileIndex + ifRange.Start + (mkPos (elifRange.StartLine - 1) sourceLines[startLineIndex].Length) + + { + Scope = Scope.HashDirective + Collapse = Collapse.Same + Range = range + CollapseRange = range + } + |> acc.Add + + group directives (elifDirective :: stack) sourceLines + | _ -> group directives stack sourceLines | ConditionalDirectiveTrivia.Else elseRange as elseDirective :: directives -> match stack with - | ConditionalDirectiveTrivia.If(_, ifRange) :: stack -> + | ConditionalDirectiveTrivia.If(_, ifRange) :: stack + | ConditionalDirectiveTrivia.Elif(_, ifRange) :: stack -> let startLineIndex = elseRange.StartLine - 2 if startLineIndex >= 0 then - // start of #if until the end of the line directly above #else + // start of #if/#elif until the end of the line directly above #else let range = mkFileIndexRange ifRange.FileIndex @@ -742,7 +768,9 @@ module Structure = | _ -> group directives stack sourceLines | ConditionalDirectiveTrivia.EndIf endIfRange :: directives -> match stack with - | ConditionalDirectiveTrivia.If(_, ifRange) :: stack -> + | ConditionalDirectiveTrivia.If(_, ifRange) :: stack + | ConditionalDirectiveTrivia.Elif(_, ifRange) :: stack + | ConditionalDirectiveTrivia.Else ifRange :: stack -> let range = Range.startToEnd ifRange endIfRange { @@ -753,18 +781,6 @@ module Structure = } |> acc.Add - group directives stack sourceLines - | ConditionalDirectiveTrivia.Else elseRange :: stack -> - let range = Range.startToEnd elseRange endIfRange - - { - Scope = Scope.HashDirective - Collapse = Collapse.Same - Range = range - CollapseRange = range - } - |> acc.Add - group directives stack sourceLines | _ -> group directives stack sourceLines diff --git a/src/Compiler/SyntaxTree/LexerStore.fs b/src/Compiler/SyntaxTree/LexerStore.fs index 8daf2125fc..6cddca067c 100644 --- a/src/Compiler/SyntaxTree/LexerStore.fs +++ b/src/Compiler/SyntaxTree/LexerStore.fs @@ -107,6 +107,23 @@ module IfdefStore = store.Add(ConditionalDirectiveTrivia.If(expr, m)) + let SaveElifHash (lexbuf: Lexbuf, lexed: string, expr: LexerIfdefExpression, range: range) = + let store = getStore lexbuf + + let expr = + let rec visit (expr: LexerIfdefExpression) : IfDirectiveExpression = + match expr with + | LexerIfdefExpression.IfdefAnd(l, r) -> IfDirectiveExpression.And(visit l, visit r) + | LexerIfdefExpression.IfdefOr(l, r) -> IfDirectiveExpression.Or(visit l, visit r) + | LexerIfdefExpression.IfdefNot e -> IfDirectiveExpression.Not(visit e) + | LexerIfdefExpression.IfdefId id -> IfDirectiveExpression.Ident id + + visit expr + + let m = mkRangeWithoutLeadingWhitespace lexed range + + store.Add(ConditionalDirectiveTrivia.Elif(expr, m)) + let SaveElseHash (lexbuf: Lexbuf, lexed: string, range: range) = let store = getStore lexbuf let m = mkRangeWithoutLeadingWhitespace lexed range diff --git a/src/Compiler/SyntaxTree/LexerStore.fsi b/src/Compiler/SyntaxTree/LexerStore.fsi index c63174a770..6fcf80ac5d 100644 --- a/src/Compiler/SyntaxTree/LexerStore.fsi +++ b/src/Compiler/SyntaxTree/LexerStore.fsi @@ -36,6 +36,8 @@ module IfdefStore = val SaveIfHash: lexbuf: Lexbuf * lexed: string * expr: LexerIfdefExpression * range: range -> unit + val SaveElifHash: lexbuf: Lexbuf * lexed: string * expr: LexerIfdefExpression * range: range -> unit + val SaveElseHash: lexbuf: Lexbuf * lexed: string * range: range -> unit val SaveEndIfHash: lexbuf: Lexbuf * lexed: string * range: range -> unit diff --git a/src/Compiler/SyntaxTree/ParseHelpers.fs b/src/Compiler/SyntaxTree/ParseHelpers.fs index 572600f9ff..500c931bb6 100644 --- a/src/Compiler/SyntaxTree/ParseHelpers.fs +++ b/src/Compiler/SyntaxTree/ParseHelpers.fs @@ -77,6 +77,7 @@ let rhs parseState i = rhs2 parseState i i type LexerIfdefStackEntry = | IfDefIf | IfDefElse + | IfDefSkipRemaining // Used when an #if or #elif branch has been taken and we're skipping remaining branches /// Represents the active #if/#else blocks type LexerIfdefStackEntries = (LexerIfdefStackEntry * range) list diff --git a/src/Compiler/SyntaxTree/ParseHelpers.fsi b/src/Compiler/SyntaxTree/ParseHelpers.fsi index 301e72e0ed..2ce4674fc5 100644 --- a/src/Compiler/SyntaxTree/ParseHelpers.fsi +++ b/src/Compiler/SyntaxTree/ParseHelpers.fsi @@ -42,6 +42,7 @@ val rhs: parseState: IParseState -> i: int -> range type LexerIfdefStackEntry = | IfDefIf | IfDefElse + | IfDefSkipRemaining // Used when an #if or #elif branch has been taken and we're skipping remaining branches type LexerIfdefStackEntries = (LexerIfdefStackEntry * range) list diff --git a/src/Compiler/SyntaxTree/SyntaxTrivia.fs b/src/Compiler/SyntaxTree/SyntaxTrivia.fs index 53ac39d536..1f7f1e44f1 100644 --- a/src/Compiler/SyntaxTree/SyntaxTrivia.fs +++ b/src/Compiler/SyntaxTree/SyntaxTrivia.fs @@ -14,6 +14,7 @@ type IdentTrivia = [] type ConditionalDirectiveTrivia = | If of expr: IfDirectiveExpression * range: range + | Elif of expr: IfDirectiveExpression * range: range | Else of range: range | EndIf of range: range diff --git a/src/Compiler/SyntaxTree/SyntaxTrivia.fsi b/src/Compiler/SyntaxTree/SyntaxTrivia.fsi index c690a6ac01..28c4dfab62 100644 --- a/src/Compiler/SyntaxTree/SyntaxTrivia.fsi +++ b/src/Compiler/SyntaxTree/SyntaxTrivia.fsi @@ -24,6 +24,7 @@ type IdentTrivia = [] type ConditionalDirectiveTrivia = | If of expr: IfDirectiveExpression * range: range + | Elif of expr: IfDirectiveExpression * range: range | Else of range: range | EndIf of range: range diff --git a/src/Compiler/lex.fsl b/src/Compiler/lex.fsl index 1f905bc049..97445394d1 100644 --- a/src/Compiler/lex.fsl +++ b/src/Compiler/lex.fsl @@ -1046,15 +1046,42 @@ rule token (args: LexArgs) (skip: bool) = parse let tok = HASH_IF(m, lexed, LexCont.EndLine(args.ifdefStack, args.stringNest, contCase)) if skip then endline contCase args skip lexbuf else tok } - | anywhite* "#else" anywhite* ("//" anystring)? + | anywhite* "#elif" anywhite+ anystring + { let m = lexbuf.LexemeRange + match args.ifdefStack with + | [] -> LEX_FAILURE (FSComp.SR.lexHashElseNoMatchingIf()) + | (IfDefElse,_) :: _rest -> LEX_FAILURE (FSComp.SR.lexHashEndifRequiredForElse()) + | (IfDefIf,_) :: rest -> + shouldStartLine args lexbuf m (FSComp.SR.lexHashElseMustBeFirst()) + let lookup id = List.contains id args.conditionalDefines + let lexed = lexeme lexbuf + let _, expr = evalIfDefExpression lexbuf.StartPos lexbuf.ReportLibraryOnlyFeatures lexbuf.LanguageVersion lexbuf.StrictIndentation args lookup lexed + IfdefStore.SaveElifHash(lexbuf, lexed, expr, m) + // Change stack to IfDefSkipRemaining to indicate a branch has been taken and we're skipping the rest + args.ifdefStack <- (IfDefSkipRemaining,m) :: rest + let tok = HASH_ELIF(m, lexed, LexCont.EndLine(args.ifdefStack, args.stringNest, LexerEndlineContinuation.IfdefSkip(0, m))) + if skip then endline (LexerEndlineContinuation.IfdefSkip(0, m)) args skip lexbuf else tok + | (IfDefSkipRemaining,_) :: _ -> + // A branch has already been taken, skip remaining elif branches + shouldStartLine args lexbuf m (FSComp.SR.lexHashElseMustBeFirst()) + let lookup id = List.contains id args.conditionalDefines + let lexed = lexeme lexbuf + let _, expr = evalIfDefExpression lexbuf.StartPos lexbuf.ReportLibraryOnlyFeatures lexbuf.LanguageVersion lexbuf.StrictIndentation args lookup lexed + IfdefStore.SaveElifHash(lexbuf, lexed, expr, m) + let tok = HASH_ELIF(m, lexed, LexCont.EndLine(args.ifdefStack, args.stringNest, LexerEndlineContinuation.IfdefSkip(0, m))) + if skip then endline (LexerEndlineContinuation.IfdefSkip(0, m)) args skip lexbuf else tok } + + | anywhite* "#else" anywhite* ("//" anystring)? { let lexed = (lexeme lexbuf) + let m = lexbuf.LexemeRange match args.ifdefStack with | [] -> LEX_FAILURE (FSComp.SR.lexHashElseNoMatchingIf()) | (IfDefElse,_) :: _rest -> LEX_FAILURE (FSComp.SR.lexHashEndifRequiredForElse()) - | (IfDefIf,_) :: rest -> - let m = lexbuf.LexemeRange + | (IfDefSkipRemaining as operation,_) :: rest // A branch has already been taken, skip the else branch + | (IfDefIf as operation,_) :: rest -> shouldStartLine args lexbuf m (FSComp.SR.lexHashElseMustBeFirst()) - args.ifdefStack <- (IfDefElse,m) :: rest + if operation = IfDefIf then + args.ifdefStack <- (IfDefElse,m) :: rest IfdefStore.SaveElseHash(lexbuf, lexed, m) let tok = HASH_ELSE(m, lexed, LexCont.EndLine(args.ifdefStack, args.stringNest, LexerEndlineContinuation.IfdefSkip(0, m))) if skip then endline (LexerEndlineContinuation.IfdefSkip(0, m)) args skip lexbuf else tok } @@ -1072,12 +1099,14 @@ rule token (args: LexArgs) (skip: bool) = parse if not skip then tok else endline LexerEndlineContinuation.Token args skip lexbuf } | "#if" + | "#elif" { let tok = WHITESPACE (LexCont.Token (args.ifdefStack, args.stringNest)) let tok = fail args lexbuf (FSComp.SR.lexHashIfMustHaveIdent()) tok if skip then token args skip lexbuf else tok } // Let the parser deal with these invalid directives | anywhite* "#if" ident_char+ + | anywhite* "#elif" ident_char+ | anywhite* "#else" ident_char+ | anywhite* "#endif" ident_char+ | anywhite* "#light" ident_char+ @@ -1118,6 +1147,47 @@ and ifdefSkip (n: int) (m: range) (args: LexArgs) (skip: bool) = parse let tok = INACTIVECODE(LexCont.EndLine(args.ifdefStack, args.stringNest, LexerEndlineContinuation.IfdefSkip(n+1, m))) if skip then endline (LexerEndlineContinuation.IfdefSkip(n+1, m)) args skip lexbuf else tok } + | anywhite* "#elif" anywhite+ anystring + { let m = lexbuf.LexemeRange + + // If #elif is the first thing on the line then process it, otherwise ignore, because it is invalid (e.g. "(**) #elif ...") + if (m.StartColumn <> 0) then + if not skip then INACTIVECODE (LexCont.IfDefSkip(args.ifdefStack, args.stringNest, n, m)) + else ifdefSkip n m args skip lexbuf + elif n = 0 then + match args.ifdefStack with + | []-> LEX_FAILURE (FSComp.SR.lexHashElseNoMatchingIf()) + | (IfDefElse,_) :: _rest -> LEX_FAILURE (FSComp.SR.lexHashEndifRequiredForElse()) + | (IfDefSkipRemaining,_) :: _ -> + // A branch has already been taken, skip remaining branches + let lexed = lexeme lexbuf + let lookup id = List.contains id args.conditionalDefines + let _, expr = evalIfDefExpression lexbuf.StartPos lexbuf.ReportLibraryOnlyFeatures lexbuf.LanguageVersion lexbuf.StrictIndentation args lookup lexed + IfdefStore.SaveElifHash(lexbuf, lexed, expr, m) + if not skip then INACTIVECODE(LexCont.EndLine(args.ifdefStack, args.stringNest, LexerEndlineContinuation.IfdefSkip(0, m))) + else endline (LexerEndlineContinuation.IfdefSkip(0, m)) args skip lexbuf + | (IfDefIf,_) :: rest -> + let lexed = lexeme lexbuf + let lookup id = List.contains id args.conditionalDefines + let isTrue, expr = evalIfDefExpression lexbuf.StartPos lexbuf.ReportLibraryOnlyFeatures lexbuf.LanguageVersion lexbuf.StrictIndentation args lookup lexed + IfdefStore.SaveElifHash(lexbuf, lexed, expr, m) + if isTrue then + // Condition is true, change stack to IfDefSkipRemaining and resume normal parsing + args.ifdefStack <- (IfDefSkipRemaining,m) :: rest + if not skip then HASH_ELIF(m, lexed, LexCont.EndLine(args.ifdefStack, args.stringNest, LexerEndlineContinuation.Token)) + else endline LexerEndlineContinuation.Token args skip lexbuf + else + // Condition is false, continue skipping + if not skip then INACTIVECODE(LexCont.EndLine(args.ifdefStack, args.stringNest, LexerEndlineContinuation.IfdefSkip(0, m))) + else endline (LexerEndlineContinuation.IfdefSkip(0, m)) args skip lexbuf + else + let lexed = lexeme lexbuf + let lookup id = List.contains id args.conditionalDefines + let _, expr = evalIfDefExpression lexbuf.StartPos lexbuf.ReportLibraryOnlyFeatures lexbuf.LanguageVersion lexbuf.StrictIndentation args lookup lexed + IfdefStore.SaveElifHash(lexbuf, lexed, expr, m) + if not skip then INACTIVECODE(LexCont.EndLine(args.ifdefStack, args.stringNest, LexerEndlineContinuation.IfdefSkip(n, m))) + else endline (LexerEndlineContinuation.IfdefSkip(n, m)) args skip lexbuf } + | anywhite* "#else" anywhite* ("//" anystring)? { let lexed = (lexeme lexbuf) let m = lexbuf.LexemeRange @@ -1130,6 +1200,11 @@ and ifdefSkip (n: int) (m: range) (args: LexArgs) (skip: bool) = parse match args.ifdefStack with | []-> LEX_FAILURE (FSComp.SR.lexHashElseNoMatchingIf()) | (IfDefElse,_) :: _rest -> LEX_FAILURE (FSComp.SR.lexHashEndifRequiredForElse()) + | (IfDefSkipRemaining,_) :: _ -> + // A branch has already been taken, skip remaining branches + IfdefStore.SaveElseHash(lexbuf, lexed, m) + if not skip then INACTIVECODE(LexCont.EndLine(args.ifdefStack, args.stringNest, LexerEndlineContinuation.IfdefSkip(0, m))) + else endline (LexerEndlineContinuation.IfdefSkip(0, m)) args skip lexbuf | (IfDefIf,_) :: rest -> let m = lexbuf.LexemeRange IfdefStore.SaveElseHash(lexbuf, lexed, m) diff --git a/src/Compiler/pars.fsy b/src/Compiler/pars.fsy index 172bd9683e..1e920c1315 100644 --- a/src/Compiler/pars.fsy +++ b/src/Compiler/pars.fsy @@ -152,7 +152,7 @@ let parse_error_rich = Some(fun (ctxt: ParseErrorContext<_>) -> /* These are artificial */ %token LEX_FAILURE %token COMMENT WHITESPACE HASH_LINE HASH_LIGHT INACTIVECODE LINE_COMMENT STRING_TEXT EOF -%token HASH_IF HASH_ELSE HASH_ENDIF WARN_DIRECTIVE +%token HASH_IF HASH_ELIF HASH_ELSE HASH_ENDIF WARN_DIRECTIVE %start signatureFile implementationFile interaction typedSequentialExprEOF typEOF %type typedSequentialExprEOF diff --git a/tests/FSharp.Compiler.ComponentTests/CompilerDirectives/Ifdef.fs b/tests/FSharp.Compiler.ComponentTests/CompilerDirectives/Ifdef.fs index 99d019504d..39e3ce12e2 100644 --- a/tests/FSharp.Compiler.ComponentTests/CompilerDirectives/Ifdef.fs +++ b/tests/FSharp.Compiler.ComponentTests/CompilerDirectives/Ifdef.fs @@ -54,4 +54,201 @@ module A FSharp sourceUnknownHash |> compile - |> shouldSucceed \ No newline at end of file + |> shouldSucceed + + // #elif tests + let elifSource1 = """ +[] +let main _ = + let result = + #if DEFINE1 + 1 + #elif DEFINE2 + 2 + #elif DEFINE3 + 3 + #else + 4 + #endif + result +""" + + [] + [] + [] + [] + [] + let elifBasicTest (mydefine, expectedExitCode) = + let defines = if mydefine = "NONE" then [] else [mydefine] + FSharp elifSource1 + |> withDefines defines + |> compileExeAndRun + |> withExitCode expectedExitCode + + let elifSource2 = """ +[] +let main _ = + let result = + #if DEFINE1 + 1 + #elif DEFINE2 && DEFINE3 + 2 + #else + 3 + #endif + result +""" + + [] + let elifWithComplexExpression () = + FSharp elifSource2 + |> withDefines ["DEFINE2"; "DEFINE3"] + |> compileExeAndRun + |> withExitCode 2 + + [] + let elifWithComplexExpressionFalse () = + FSharp elifSource2 + |> withDefines ["DEFINE2"] + |> compileExeAndRun + |> withExitCode 3 + + let elifNestedSource = """ +[] +let main _ = + let result = + #if OUTER + #if INNER + 1 + #elif INNER2 + 2 + #else + 3 + #endif + #elif OUTER2 + 4 + #else + 5 + #endif + result +""" + + [] + let elifNested () = + FSharp elifNestedSource + |> withDefines ["OUTER"; "INNER2"] + |> compileExeAndRun + |> withExitCode 2 + + [] + let elifNestedOuter () = + FSharp elifNestedSource + |> withDefines ["OUTER2"] + |> compileExeAndRun + |> withExitCode 4 + + let elifMultipleSource = """ +[] +let main _ = + let result = + #if DEFINE1 + 1 + #elif DEFINE2 + 2 + #elif DEFINE3 + 3 + #elif DEFINE4 + 4 + #elif DEFINE5 + 5 + #else + 6 + #endif + result +""" + + [] + let elifMultiple () = + FSharp elifMultipleSource + |> withDefines ["DEFINE4"] + |> compileExeAndRun + |> withExitCode 4 + + let elifAfterElseSource = """ +#if DEFINE1 +let x = 1 +#else +let x = 2 +#elif DEFINE2 +let x = 3 +#endif +""" + + [] + let elifAfterElseError () = + FSharp elifAfterElseSource + |> withDefines ["DEFINE2"] + |> asExe + |> compile + |> withDiagnosticMessage "#endif required for #else in implementation file" + + let elifNoMatchingIfSource = """ +#elif DEFINE1 +let x = 1 +#endif +""" + + [] + let elifNoMatchingIf () = + FSharp elifNoMatchingIfSource + |> asExe + |> compile + |> withDiagnosticMessage "#else has no matching #if in implementation file" + + let elifWithOrExpression = """ +[] +let main _ = + let result = + #if DEFINE1 + 1 + #elif DEFINE2 || DEFINE3 + 2 + #else + 3 + #endif + result +""" + + [] + let elifWithOrTrue () = + FSharp elifWithOrExpression + |> withDefines ["DEFINE3"] + |> compileExeAndRun + |> withExitCode 2 + + let elifWithNotExpression = """ +[] +let main _ = + let result = + #if DEFINE1 + 1 + #elif !DEFINE2 + 2 + #else + 3 + #endif + result +""" + + [] + let elifWithNotTrue () = + FSharp elifWithNotExpression + |> compileExeAndRun + |> withExitCode 2 + + [] + let elifWithNotFalse () = + FSharp elifWithNotExpression + |> withDefines ["DEFINE2"] + |> compileExeAndRun + |> withExitCode 3 \ No newline at end of file