@@ -13,6 +13,7 @@ open FSharp.Compiler.Text
1313open FSharp.Compiler .Text .Position
1414open FSharp.Compiler .Text .Range
1515open FSharp.Compiler .Xml
16+ open Internal.Utilities .Library
1617open Internal.Utilities .Text .Lexing
1718open Internal.Utilities .Text .Parsing
1819
@@ -860,3 +861,198 @@ let mkSynTypeTuple (elementTypes: SynTupleTypeSegment list) : SynType =
860861 ||> List.fold ( fun acc segment -> unionRanges acc segment.Range)
861862
862863 SynType.Tuple( false , elementTypes, range)
864+
865+ #if DEBUG
866+ let debugPrint s =
867+ if Internal.Utilities.Text.Parsing.Flags.debug then
868+ printfn " \n %s " s
869+ #else
870+ let debugPrint s = ignore s
871+ #endif
872+
873+ let exprFromParseError ( e : SynExpr ) = SynExpr.FromParseError( e, e.Range)
874+
875+ let patFromParseError ( e : SynPat ) = SynPat.FromParseError( e, e.Range)
876+
877+ // record bindings returned by the recdExprBindings rule has shape:
878+ // (binding, separator-before-this-binding)
879+ // this function converts arguments from form
880+ // binding1 (binding2*sep1, binding3*sep2...) sepN
881+ // to form
882+ // binding1*sep1, binding2*sep2
883+ let rebindRanges first fields lastSep =
884+ let rec run ( name , mEquals , value ) l acc =
885+ match l with
886+ | [] -> List.rev ( SynExprRecordField( name, mEquals, value, lastSep) :: acc)
887+ | ( f, m) :: xs -> run f xs ( SynExprRecordField( name, mEquals, value, m) :: acc)
888+
889+ run first fields []
890+
891+ let mkUnderscoreRecdField m =
892+ SynLongIdent([ ident ( " _" , m) ], [], [ None ]), false
893+
894+ let mkRecdField ( lidwd : SynLongIdent ) = lidwd, true
895+
896+ // Used for 'do expr' in a class.
897+ let mkSynDoBinding ( vis : SynAccess option , expr , m ) =
898+ match vis with
899+ | Some vis -> errorR ( Error( FSComp.SR.parsDoCannotHaveVisibilityDeclarations ( vis.ToString()), m))
900+ | None -> ()
901+
902+ SynBinding(
903+ None,
904+ SynBindingKind.Do,
905+ false ,
906+ false ,
907+ [],
908+ PreXmlDoc.Empty,
909+ SynInfo.emptySynValData,
910+ SynPat.Const( SynConst.Unit, m),
911+ None,
912+ expr,
913+ m,
914+ DebugPointAtBinding.NoneAtDo,
915+ SynBindingTrivia.Zero
916+ )
917+
918+ let mkSynExprDecl ( e : SynExpr ) = SynModuleDecl.Expr( e, e.Range)
919+
920+ let addAttribs attrs p = SynPat.Attrib( p, attrs, p.Range)
921+
922+ let unionRangeWithPos ( r : range ) p =
923+ let r2 = mkRange r.FileName p p
924+ unionRanges r r2
925+
926+ /// Report a good error at the end of file, e.g. for non-terminated strings
927+ let checkEndOfFileError t =
928+ match t with
929+ | LexCont.IfDefSkip (_, _, _, m) -> reportParseErrorAt m ( FSComp.SR.parsEofInHashIf ())
930+
931+ | LexCont.String (_, _, LexerStringStyle.SingleQuote, kind, m) ->
932+ if kind.IsInterpolated then
933+ reportParseErrorAt m ( FSComp.SR.parsEofInInterpolatedString ())
934+ else
935+ reportParseErrorAt m ( FSComp.SR.parsEofInString ())
936+
937+ | LexCont.String (_, _, LexerStringStyle.TripleQuote, kind, m) ->
938+ if kind.IsInterpolated then
939+ reportParseErrorAt m ( FSComp.SR.parsEofInInterpolatedTripleQuoteString ())
940+ else
941+ reportParseErrorAt m ( FSComp.SR.parsEofInTripleQuoteString ())
942+
943+ | LexCont.String (_, _, LexerStringStyle.Verbatim, kind, m) ->
944+ if kind.IsInterpolated then
945+ reportParseErrorAt m ( FSComp.SR.parsEofInInterpolatedVerbatimString ())
946+ else
947+ reportParseErrorAt m ( FSComp.SR.parsEofInVerbatimString ())
948+
949+ | LexCont.Comment (_, _, _, m) -> reportParseErrorAt m ( FSComp.SR.parsEofInComment ())
950+
951+ | LexCont.SingleLineComment (_, _, _, m) -> reportParseErrorAt m ( FSComp.SR.parsEofInComment ())
952+
953+ | LexCont.StringInComment (_, _, LexerStringStyle.SingleQuote, _, m) -> reportParseErrorAt m ( FSComp.SR.parsEofInStringInComment ())
954+
955+ | LexCont.StringInComment (_, _, LexerStringStyle.Verbatim, _, m) ->
956+ reportParseErrorAt m ( FSComp.SR.parsEofInVerbatimStringInComment ())
957+
958+ | LexCont.StringInComment (_, _, LexerStringStyle.TripleQuote, _, m) ->
959+ reportParseErrorAt m ( FSComp.SR.parsEofInTripleQuoteStringInComment ())
960+
961+ | LexCont.MLOnly (_, _, m) -> reportParseErrorAt m ( FSComp.SR.parsEofInIfOcaml ())
962+
963+ | LexCont.EndLine (_, _, LexerEndlineContinuation.Skip (_, m)) -> reportParseErrorAt m ( FSComp.SR.parsEofInDirective ())
964+
965+ | LexCont.EndLine ( endifs, nesting, LexerEndlineContinuation.Token)
966+ | LexCont.Token ( endifs, nesting) ->
967+ match endifs with
968+ | [] -> ()
969+ | (_, m) :: _ -> reportParseErrorAt m ( FSComp.SR.parsNoHashEndIfFound ())
970+
971+ match nesting with
972+ | [] -> ()
973+ | (_, _, m) :: _ -> reportParseErrorAt m ( FSComp.SR.parsEofInInterpolatedStringFill ())
974+
975+ type BindingSet = BindingSetPreAttrs of range * bool * bool * ( SynAttributes -> SynAccess option -> SynAttributes * SynBinding list ) * range
976+
977+ let mkClassMemberLocalBindings
978+ (
979+ isStatic ,
980+ initialRangeOpt ,
981+ attrs ,
982+ vis ,
983+ BindingSetPreAttrs ( _ , isRec , isUse , declsPreAttrs , bindingSetRange )
984+ ) =
985+ let ignoredFreeAttrs , decls = declsPreAttrs attrs vis
986+
987+ let mWhole =
988+ match initialRangeOpt with
989+ | None -> bindingSetRange
990+ | Some m -> unionRanges m bindingSetRange
991+ // decls could have a leading attribute
992+ |> fun m -> ( m, decls) ||> unionRangeWithListBy ( fun ( SynBinding ( range = m )) -> m)
993+
994+ if not ( isNil ignoredFreeAttrs) then
995+ warning ( Error( FSComp.SR.parsAttributesIgnored (), mWhole))
996+
997+ if isUse then
998+ errorR ( Error( FSComp.SR.parsUseBindingsIllegalInImplicitClassConstructors (), mWhole))
999+
1000+ SynMemberDefn.LetBindings( decls, isStatic, isRec, mWhole)
1001+
1002+ let mkLocalBindings ( mWhole , BindingSetPreAttrs ( _ , isRec , isUse , declsPreAttrs , _ ), mIn , body : SynExpr ) =
1003+ let ignoredFreeAttrs , decls = declsPreAttrs [] None
1004+
1005+ let mWhole =
1006+ match decls with
1007+ | SynBinding ( xmlDoc = xmlDoc) :: _ -> unionRangeWithXmlDoc xmlDoc mWhole
1008+ | _ -> mWhole
1009+
1010+ if not ( isNil ignoredFreeAttrs) then
1011+ warning ( Error( FSComp.SR.parsAttributesIgnored (), mWhole))
1012+
1013+ let mIn =
1014+ mIn
1015+ |> Option.bind ( fun ( mIn : range ) ->
1016+ if Position.posEq mIn.Start body.Range.Start then
1017+ None
1018+ else
1019+ Some mIn)
1020+
1021+ SynExpr.LetOrUse( isRec, isUse, decls, body, mWhole, { InKeyword = mIn })
1022+
1023+ let mkDefnBindings ( mWhole , BindingSetPreAttrs ( _ , isRec , isUse , declsPreAttrs , _bindingSetRange ), attrs , vis , attrsm ) =
1024+ if isUse then
1025+ warning ( Error( FSComp.SR.parsUseBindingsIllegalInModules (), mWhole))
1026+
1027+ let freeAttrs , decls = declsPreAttrs attrs vis
1028+ // decls might have an extended range due to leading attributes
1029+ let mWhole =
1030+ ( mWhole, decls) ||> unionRangeWithListBy ( fun ( SynBinding ( range = m )) -> m)
1031+
1032+ let letDecls = [ SynModuleDecl.Let( isRec, decls, mWhole) ]
1033+
1034+ let attrDecls =
1035+ if not ( isNil freeAttrs) then
1036+ [ SynModuleDecl.Attributes( freeAttrs, attrsm) ]
1037+ else
1038+ []
1039+
1040+ attrDecls @ letDecls
1041+
1042+ let idOfPat ( parseState : IParseState ) m p =
1043+ match p with
1044+ | SynPat.Wild r when parseState.LexBuffer.SupportsFeature LanguageFeature.WildCardInForLoop -> mkSynId r " _"
1045+ | SynPat.Named ( SynIdent ( id, _), false , _, _) -> id
1046+ | SynPat.LongIdent ( longDotId = SynLongIdent ([ id ], _, _); typarDecls = None; argPats = SynArgPats.Pats []; accessibility = None) ->
1047+ id
1048+ | _ -> raiseParseErrorAt m ( FSComp.SR.parsIntegerForLoopRequiresSimpleIdentifier ())
1049+
1050+ let checkForMultipleAugmentations m a1 a2 =
1051+ if not ( isNil a1) && not ( isNil a2) then
1052+ raiseParseErrorAt m ( FSComp.SR.parsOnlyOneWithAugmentationAllowed ())
1053+
1054+ a1 @ a2
1055+
1056+ let rangeOfLongIdent ( lid : LongIdent ) =
1057+ System.Diagnostics.Debug.Assert( not lid.IsEmpty, " the parser should never produce a long-id that is the empty list" )
1058+ ( lid.Head.idRange, lid) ||> unionRangeWithListBy ( fun id -> id.idRange)
0 commit comments