Rodrigo Werneck · Sep 11, 2017 go to post

For CSP/Zen sessions shouldn´t $mvv(58) be set as the Accept-Language sent by the User-Agent? It is not. Why?

Rodrigo Werneck · Sep 11, 2017 go to post

Hi, Robert!

User-agent is sending:

Accept-Language: pt-BR,pt;q=0.8,en-US;q=0.5,en;q=0.3

But %session.Language is being seen with the value "en", when not explicitly set by the application.

In ^%qCacheMessage global we´ve got entries for pt-br.
I want, for example, that the "No Results" text for the ZEN tablePane tag when there is no row returned is exhibited in portuguese as provisioned by the factory entry below:

^%qCacheMsg("%ZEN","pt-br",3559354800)="Nenhum resultado"
How to?

Rodrigo Werneck · Sep 11, 2017 go to post

I´m not using $$$Text by myself. The "No Results" string is shown by ZEN tablePane itself, which is through $$$Text:

%ZEN.Component.tablePane.cls

If ((tRow = 0)&&(..initialExecute)) {
#; draw indicator of no results (unless deferred executed)
Set msgNoResults = $$$Text("No Results","%ZEN")
 

How do I include a language in Caché NLS definition?

Rodrigo Werneck · Sep 12, 2017 go to post

The Mgmt Portal works with a explicit definition by the user of which is his/her preferred language.

There it is working correctly when I choose Portuguese (Brazil).

The problem seems to be with the treatment of the Accept-Language HTTP header by CSP, which IMHO should be seting $mvv(58) accordingly, and it is not.

Rodrigo Werneck · Mar 20, 2018 go to post

Sorry, [0-9]+ indeed (I was testing with GNU grep -o with '*' and results are the same).

Thanks

Rodrigo Werneck · Feb 13, 2019 go to post

It´s beem 18 months and Itersystems did not come with any solution such as Rubens´ suggestion to this common need yet?

Rodrigo Werneck · Dec 3, 2021 go to post

It´s really curious that nobody yet has create such a converter. I´ve been thinking of it for years, but once I start thinking of all the possibilities a real parser needed for this got to treat, I give up.
Dot syntax (argumentless do) and one letter commands (and a lot of them in the same line) was very tempting and addictive on those old days.
But now, the new generation which got all those more modern equivalent and ubiquitous styles for flow control, which althought much less terse than the one-line program style of old days is much less prone to errors as the code evolves, should not need to learn to read and to write in that cryptic dialet.
Not anyone at all in ISC was ever tempted with the idea of this dot2braces converter?
 

Rodrigo Werneck · Dec 5, 2021 go to post

But don´t you think that code written with one letter commands can be read a liitle bit faster than otherwise?

Considering the last conversion example you forgot the need to treat all que quits (generally with postconditionals) which tend to occur inside argumentless do blocks. I´m dealing with them right now in my first dot2braces procedure. I am going to convert them into If '(condition) { ... }. 

I´ve first tried justo to convert do to do { ... } while 0 so as the quits could be preserved untouched.
But in my first candidate test routine I faced a not unusual "I Condition D" which could be converted by also converting the old style I(f) to new style just adding another pair of braces. But I´ve also run uppon a "I Condition D ... E ", which demands that the Else is also converted to the new style.

Any better idea?
 

Rodrigo Werneck · Dec 10, 2021 go to post

I used the %SyntaxColor help to identify each command in a line and the aproach of converting DO  to DO { ... } While 0 in order to leave the QUITs untouched.

%zDot2Braces(routine,indent=4)
    NEW (routine,indent)
    SET S=$CHAR(127)
    SET lineNumber=0
    KILL level
    SET level=0
    SET rm=##class(%Regex.Matcher).%New("dummy")
    KILL postCommands,whileLoop
    SET sc=##class(%Atelier.v2.Utils.TextServices).GetTextAsArray(routine,0,.moduleTextArray)
    IF 'sc DO $system.OBJ.DisplayError(sc)
    KILL:moduleTextArray(1)?1"ROUTINE [Type=".moduleTextArray(1)
    SET instr=##class(%Stream.TmpCharacter).%New()
    FOR  {
        SET lineNumber=$order(moduleTextArray(lineNumber),1,line) 
        QUIT:lineNumber=""
        QUIT:lineNumber'=+lineNumber
        DO instr.WriteLine(line)
    }
    SET colorer=##class(%SyntaxColor).%New()
    SET outstr=##class(%Stream.TmpCharacter).%New()
    SET sc=colorer.Color(instr,outstr,$select($zconvert($piece(routine,".",*),"U")="CLS":"CLS",1:"COS"),"Q=N",,,.langs,.coloringerrors)
    IF 'sc {
        WRITE "Fatal error: ",colorer.DLLResultCode,!
        Return
    }
    IF coloringerrors 
        WRITE "Syntax error(s)",!
        Return
    }
    Set lastPostCommands=""
    FOR lineNumber=1:1 {
        SET line=$$getParsedLine(.cmdpos)
        QUIT:line=-1
        SET midCode=""
        SET lineLevel=$$lineLevel(line)
        FOR i=1:1:$length(line) quit:" "_$CHAR(9)'[$EXTRACT(line,i)
        SET lineMargin=$extract(line,1,i-1),line=$extract(line,i,*)
        Set postDone=""
        WHILE lineLevel<level {
            Set lastLineMargin=$P(level(level),S,2)
            FOR i=1:1:$P(level(level),S,1) {
                WRITE lastLineMargin,$justify("",(level-1)*indent),$s(lineMargin=""&(level'>1):" ",1:""),"}"
                IF $get(whileLoop(level)) {
                    WRITE " While 0"
                    KILL whileLoop(level)
                    IF $LENGTH($zstrip($get(postCommands(level)),"<>W")) {
                        WRITE !,lastLineMargin,$justify("",(level)*indent),postCommands(level)
                        Set lastPostCommands=postCommands(level)
                        KILL postCommands(level)
                    }
                }    
                WRITE !
            }
            SET level=level-1
            Set postDone=1
        }
        SET line=$$codeQuotedSpaces(line)
        SET posDo=$locate(line,"\b[dD][oO]? ")
        SET:'posDo posDo=$locate(line,"\b[dD][oO]? *$")
        SET:'posDo posDo=$locate(line,"\b[dD][oO]?:[^ ]+ ")
        SET:'posDo posDo=$locate(line,"\b[dD][oO]?:[^ ]+ *$")
        Set nextCmd=""
        SET braceLevel=0
        IF posDo||(cmdpos && ('$G(cmdpos("FCWB"))&&("iIeE"[$extract(line,$o(cmdpos(""))-$length(lineMargin))))) {
            IF cmdpos>1 {
                SET cpos=9999,posEndCmd=$select($data(cmdpos("E"),payloadEnd):payloadEnd,1:$length(lineMargin_line))
                Set originalLine=line
                Set oldElse=""
                Set lastCmd=1
                FOR {
                    SET cpos=$order(cmdpos(cpos),-1)
                    QUIT:cpos=""
                    Set cmd=$extract(line,cpos-$length(lineMargin),posEndCmd-$length(lineMargin))
                    IF ('posDo||((cpos-$length(lineMargin))<posDo))&("iIfF"[$extract(cmd))&('lastCmd!'$locate(cmd,"[iI][fF]? 1")) {
                        SET $extract(line,posEndCmd-$length(lineMargin)) = $extract(line,posEndCmd-$length(lineMargin))_" { "
                        SET braceLevel=braceLevel + 1
                    }
                    IF $locate(cmd,"[eE]([lL][sS][eE])? ") {
                        IF $locate(lastPostCommands,"\b[iI][fF]? ") {
                            IF nextCmd?1(1"i",1"I").{
                                SET $extract(line,cpos-$length(lineMargin),cpos-$length(lineMargin)+$length(cmd)+$length(nextCmd))="If '$Test , "
                            }
                            ELSE {
                                SET $extract(line,cpos-$length(lineMargin),cpos-$length(lineMargin)+$length(cmd)-1)="If '$Test { "
                                SET braceLevel=braceLevel + 1
                            }
                        }
                        ELSE {
                            IF nextCmd?1(1"i",1"I").{
                                SET $extract(line,cpos-$length(lineMargin),cpos-$length(lineMargin)+$length(cmd)+$length(nextCmd))="ElseIf "
                            }
                            ELSE {
                                SET $extract(line,cpos-$length(lineMargin),cpos-$length(lineMargin)+$length(cmd)-1)="Else { "
                                SET braceLevel=braceLevel + 1
                            }
                        }
                        Set lastPostCommands = ""
                        SET:1 oldElse=1
                    }
                    Set nextCmd=""
                    FOR i=0:1 Set carCmd=$extract(line,cpos+i-$length(lineMargin)) q:carCmd'?1A  SET nextCmd=nextCmd_carCmd
                    SET posEndCmd = cpos - 1
                    SET lastCmd = 0
                }
                ; Set:postDone&'posDo&'oldElse line=originalLine,braceLevel=0
            }
            If posDo {
                SET posFor=$locate(line,"\b[fF]([oO][rR])? .*")
                SET:'posFor posFor=$locate(line,"\b[fF]([oO][rR])? [%A-Za-z][A-Za-z0-9]* ?=")
                FOR pat="\b[dD][oO]? ","\b[dD][oO]?:([^ ]+) ","\b[dD][oO]? *$","\b[dD][oO]?:([^ ]+) *$" {
                  SET rm.Pattern=pat
                  SET rm.Text=line
                  SET line=rm.ReplaceFirst($select($find(pat,":"):"If $1 { ",1:"")_"Do {")
                  SET:rm.Locate(1) braceLevel=braceLevel+$select($find(pat,":"):2,1:1)
                  SET whileLoop(level+1)=1
                }
                SET postCommands(level+1) = $translate($piece(line,"{",*),S," ")
                SET line=$piece(line,"{",1,*-1)_"{ "
            }
        }
        SET line=$translate(line,S," ")
        WRITE $replace(lineMargin_$JUSTIFY("",level*indent)_$zstrip($piece(line,".",level+1,*),"<W"),$char(9)," "),!
        WRITE:$LENGTH(midCode) $replace(lineMargin_$JUSTIFY("",(level+1)*indent)_midCode,$CHAR(9)," "),!
        SET:posDo!(braceLevel) level=level+1,level(level)=braceLevel_S_lineMargin
    }
    QUIT
    
lineLevel(line)
    NEW (line)
    SET line=$translate(line," "_$CHAR(9),"")
    FOR i=1:1 quit:$extract(line,i)'="."
    QUIT i-1codeQuotedSpaces(line)
    NEW (line)
    SET S=$CHAR(127)
    SET quoting=""
    FOR i=1:1:$length(line) 
        SET c=$extract(line,i) 
        IF c="""" {
            SET quoting='quoting
        }
        ElseIf c=" "&quoting {
            SET c=S
        }
        SET $extract(line,i)=c
    }
    QUIT linegetParsedLine(vetpos)
    KILL vetpos
    Set vetpos=0
    SET recLine="",cmdCount=0
    
    Do {
        SET token=$zstrip(outstr.ReadLine(),"<>W")
    WHILE token'="<line>"&'outstr.AtEnd
    
    RETURN:outstr.AtEnd -1
    
    FOR {
        SET token=$zstrip(outstr.ReadLine(),"<>W")
        QUIT:outstr.AtEnd
        QUIT:token="</line>"
        SET rm.Pattern="<([^>]*)>(.*)<\/([^>]*)>$"
        IF rm.Match(token) {
            SET:rm.Group(1)="Command" vetpos($LENGTH(recLine)+1)="",cmdCount = cmdCount+1
            Set:rm.Group(1)="Comment" vetpos("E")=$LENGTH(recLine)
            Set:(cmdCount=1)&(rm.Group(1)="Brace")&(rm.Group(2)="{") vetpos("FCWB")=1
            SET recLine = recLine_$ZCONVERT(rm.Group(2),"I","HTML")
        }
    }
    
    SET vetpos=cmdCount
    
    RETURN recLine

Sample of resulting convertion of JRNDUMP.int:

Rodrigo Werneck · Jan 17, 2022 go to post

Two bug fixes:

  1. Reset $Test wherever needed
  2. Adjust position of posts commands in the case of IF ... DO:
%zDot2Braces(routine,indent=4)
    NEW (routine,indent)
    SET S=$CHAR(127)
    SET lineNumber=0
    KILL level
    SET level=0
    SET rm=##class(%Regex.Matcher).%New("dummy")
    KILL postCommands,whileLoop
    SET sc=##class(%Atelier.v2.Utils.TextServices).GetTextAsArray(routine,0,.moduleTextArray)
    IF 'sc DO $system.OBJ.DisplayError(sc)
    KILL:moduleTextArray(1)?1"ROUTINE [Type=".moduleTextArray(1)
    SET instr=##class(%Stream.TmpCharacter).%New()
    FOR  {
        SET lineNumber=$order(moduleTextArray(lineNumber),1,line) 
        QUIT:lineNumber=""
        QUIT:lineNumber'=+lineNumber
        DO instr.WriteLine(line)
    }
    SET colorer=##class(%SyntaxColor).%New()
    SET outstr=##class(%Stream.TmpCharacter).%New()
    SET sc=colorer.Color(instr,outstr,$select($zconvert($piece(routine,".",*),"U")="CLS":"CLS",1:"COS"),"Q=N",,,.langs,.coloringerrors)
    IF 'sc {
        WRITE "Fatal error: ",colorer.DLLResultCode,!
        Return
    }
    IF coloringerrors 
        WRITE "Syntax error(s)",!
        Return
    }
    Set lastPostCommands=""
    FOR lineNumber=1:1 {
        SET line=$$getParsedLine(.cmdpos)
        QUIT:line=-1
        SET midCode=""
        SET lineLevel=$$lineLevel(line)
        FOR i=1:1:$length(line) quit:" "_$CHAR(9)'[$EXTRACT(line,i)
        SET lineMargin=$extract(line,1,i-1),line=$extract(line,i,*)
        Set postDone=""
        WHILE lineLevel<level {
            Set lastLineMargin=$P(level(level),S,2)
            FOR i=1:1:$P(level(level),S,1) {
                WRITE lastLineMargin,$justify("",(level-1)*indent),$select(lastLineMargin=""&(level'>1):" ",1:""),"}"
                IF $get(whileLoop(level)) {
                    WRITE " While 0"
                    KILL whileLoop(level)
                }    
                IF i=($P(level(level),S,1)-1),$LENGTH($zstrip($get(postCommands(level)),"<>W")) {
                    WRITE !,lastLineMargin,$justify("",(level)*indent),postCommands(level)
                    Set lastPostCommands=postCommands(level)
                    KILL postCommands(level)
                }
                WRITE !
            }
            SET level=level-1
            Set postDone=1
        }
        SET line=$$codeQuotedSpaces(line)
        SET posDo=$locate(line,"\b[dD][oO]? ")
        SET:'posDo posDo=$locate(line,"\b[dD][oO]? *$")
        SET:'posDo posDo=$locate(line,"\b[dD][oO]?:[^ ]+ ")
        SET:'posDo posDo=$locate(line,"\b[dD][oO]?:[^ ]+ *$")
        Set nextCmd=""
        SET braceLevel=0
        IF posDo||(cmdpos && ('$G(cmdpos("FCWB"))&&("iIeE"[$extract(line,$o(cmdpos(""))-$length(lineMargin))))) {
            Set ELSEcmd=""
            IF cmdpos>1 {
                SET cpos=9999,posEndCmd=$select($data(cmdpos("E"),payloadEnd):payloadEnd,1:$length(lineMargin_line))
                Set originalLine=line
                Set oldElse=""
                Set lastCmd=1
                FOR {
                    SET cpos=$order(cmdpos(cpos),-1)
                    QUIT:cpos=""
                    Set cmd=$extract(line,cpos-$length(lineMargin),posEndCmd-$length(lineMargin))
                    IF ('posDo||((cpos-$length(lineMargin))<posDo))&("iIfF"[$extract(cmd))&('lastCmd!'$locate(cmd,"[iI][fF]? 1")) {
                        SET $extract(line,posEndCmd-$length(lineMargin)) = $extract(line,posEndCmd-$length(lineMargin))_" { "
                        SET braceLevel=braceLevel + 1
                    }
                    IF $locate(cmd,"[eE]([lL][sS][eE])? ") {
                        IF $locate(lastPostCommands,"\b[iI][fF]? ") {
                            IF nextCmd?1(1"i",1"I").{
                                SET $extract(line,cpos-$length(lineMargin),cpos-$length(lineMargin)+$length(cmd)+$length(nextCmd))="If '$Test , "
                            }
                            ELSE {
                                SET $extract(line,cpos-$length(lineMargin),cpos-$length(lineMargin)+$length(cmd)-1)="If '$Test { "
                                SET braceLevel=braceLevel + 1
                            }
                            Set ELSEcmd=1
                        }
                        ELSE {
                            IF nextCmd?1(1"i",1"I").{
                                SET $extract(line,cpos-$length(lineMargin),cpos-$length(lineMargin)+$length(cmd)+$length(nextCmd))="ElseIf "
                            }
                            ELSE {
                                SET $extract(line,cpos-$length(lineMargin),cpos-$length(lineMargin)+$length(cmd)-1)="Else { "
                                SET braceLevel=braceLevel + 1
                            }
                        }
                        Set lastPostCommands = ""
                        SET:1 oldElse=1
                    }
                    Set nextCmd=""
                    FOR i=0:1 Set carCmd=$extract(line,cpos+i-$length(lineMargin)) q:carCmd'?1A  SET nextCmd=nextCmd_carCmd
                    SET posEndCmd = cpos - 1
                    SET lastCmd = 0
                }
                ; Set:postDone&'posDo&'oldElse line=originalLine,braceLevel=0
            }
            If posDo&cmdpos {
                SET posFor=$locate(line,"\b[fF]([oO][rR])? .*")
                SET:'posFor posFor=$locate(line,"\b[fF]([oO][rR])? [%A-Za-z][A-Za-z0-9]* ?=")
                FOR pat="\b[dD][oO]? ","\b[dD][oO]?:([^ ]+) ","\b[dD][oO]? *$","\b[dD][oO]?:([^ ]+) *$" {
                  SET rm.Pattern=pat
                  SET rm.Text=line
                  SET line=rm.ReplaceFirst($select($find(pat,":"):"If $1 { ",1:"")_"Do {")
                  SET:rm.Locate(1) braceLevel=braceLevel+$select($find(pat,":"):2,1:1)
                  SET whileLoop(level+1)=1
                }
                SET postCommands(level+1) = $translate($piece(line,"{",*),S," ")
                SET line=$piece(line,"{",1,*-1)_"{ "
                IF $locate(postCommands(level+1),"\b[iI][fF]? ")&'ELSEcmd {
                    WRITE $replace(lineMargin_$JUSTIFY("",level*indent)_"Set $Test=0",$char(9)," "),!
                }
            }
        }
        SET line=$translate(line,S," ")
        WRITE $replace(lineMargin_$JUSTIFY("",level*indent)_$zstrip($piece(line,".",level+1,*),"<W"),$char(9)," "),!
        WRITE:$LENGTH(midCode) $replace(lineMargin_$JUSTIFY("",(level+1)*indent)_midCode,$CHAR(9)," "),!
        SET:posDo!(braceLevel) level=level+1,level(level)=braceLevel_S_lineMargin
    }
    QUIT
    
lineLevel(line)
    NEW (line)
    SET line=$translate(line," "_$CHAR(9),"")
    FOR i=1:1 quit:$extract(line,i)'="."
    QUIT i-1codeQuotedSpaces(line)
    NEW (line)
    SET S=$CHAR(127)
    SET quoting=""
    FOR i=1:1:$length(line) 
        SET c=$extract(line,i) 
        IF c="""" {
            SET quoting='quoting
        }
        ElseIf c=" "&quoting {
            SET c=S
        }
        SET $extract(line,i)=c
    }
    QUIT linegetParsedLine(vetpos)
    KILL vetpos
    Set vetpos=0
    SET recLine="",cmdCount=0
    
    Do {
        SET token=$zstrip(outstr.ReadLine(),"<>W")
    WHILE token'="<line>"&'outstr.AtEnd
    
    RETURN:outstr.AtEnd -1
    
    FOR {
        SET token=$zstrip(outstr.ReadLine(),"<>W")
        QUIT:outstr.AtEnd
        QUIT:token="</line>"
        SET rm.Pattern="<([^>]*)>(.*)<\/([^>]*)>$"
        IF rm.Match(token) {
            SET:rm.Group(1)="Command" vetpos($LENGTH(recLine)+1)="",cmdCount = cmdCount+1
            Set:rm.Group(1)="Comment" vetpos("E")=$LENGTH(recLine)
            Set:(cmdCount=1)&(rm.Group(1)="Brace")&(rm.Group(2)="{") vetpos("FCWB")=1
            SET recLine = recLine_$ZCONVERT(rm.Group(2),"I","HTML")
        }
    }
    
    SET vetpos=cmdCount
    
    RETURN recLine
Rodrigo Werneck · Apr 28, 2022 go to post

So isn´t there a solution for linear cost pagination with customizable filtering and ordering?

Rodrigo Werneck · Jul 17, 2023 go to post

What about this dynamic discarding of SQL criteria based on empty parameters extending %SQLQuery?
 

Class gen.SmartSQLQuery Extends%Library.SQLQuery
{

ClassMethod Func() As%SQL.StatementResult [ CodeMode = generator, ProcedureBlock = 1, ServerOnly = 1 ]
{
    set%code=0// don't generate any code if it not for a queryif%mode="method"quit$$$OK// %mode is "propertymethod" for a valid query. We don't have any way currently to detect a misuse of a query classif '$$$comMemberDefined(%class,$$$cCLASSquery,%property) quit$$$OK// Reset the formal list to the query declaration:$$$comSubMemberKeyGetLvar(formal,%class,$$$cCLASSquery,%property,$$$cQUERYmethod,%method,$$$cMETHformalspecparsed)
    $$$comMemberKeyGetLvar(qformal,%class,$$$cCLASSquery,%property,$$$cQUERYformalspecparsed)
    $$$comSubMemberKeySet(%class,$$$cCLASSquery,%property,$$$cQUERYmethod,%method,$$$cMETHformalspecparsed,formal_qformal)
    Set glbArgList = formal_qformal
    Set publicList = ""For i=1:1:$ListLength(glbArgList) {
        Set$Piece(publicList,",",i) = $List($List(glbArgList,i),1)
    }
    Set publicList = publicList _ "," _ "tStatement" _ "," _ "tResult"$$$comSubMemberKeySet(%class,$$$cCLASSquery,%property,$$$cQUERYmethod,%method,$$$cMETHpubliclist,publicList)
    set sc=$$SetOneQueryMeth^%occQuery(%class,%property,%method) quit:$$$ISERR(sc) sc

    $$$comMemberKeyGetLvar(origin,%class,$$$cCLASSquery,%property,$$$cXXXXorigin)
    $$$comMemberKeyGetLvar(query,%class,$$$cCLASSquery,%property,$$$cQUERYsqlquery)
        // preparse the query to construct the actual argument list. If more than the supported number of arguments then revert to// the non-dynamic optionset query = $zstrip(query,"<W")
    set tLines = 0for tPtr = 1:1:$Length(query,$$$NL) { set tLine = $Piece(query,$$$NL,tPtr) if tLine '= "" { set tLines = tLines + 1, tLines(tLines) = tLine } }
    set sc=$$ExpandMacros^%SYS.DynamicQuery(%class,.tLines) QUIT:$$$ISERR(sc) sc
    set SQLCODE = $$dynamic^%qaqpreparser(.tLines,.tStatementPreparsed,.tStatementArgs)
    
    $$$GENERATE($Char(9)_"try {")
    $$$GENERATE($Char(9,9)_"Set query = """_$replace(query,$$$NL,"""_$C(13,10)_""")_"""")
    $$$GENERATE($Char(9,9)_"For i=1:1:$Length(query,$$$NL) {")
    $$$GENERATE($Char(9,9,9)_"Set line=$Piece(query,$$$NL,i)")
    $$$GENERATE($Char(9,9,9)_"If line?.E1"":""1.AN {")
    $$$GENERATE($Char(9,9,9,9)_"Set var=$Piece($Piece(line,"":"",2),"" "",1)")
    $$$GENERATE($Char(9,9,9,9)_"if @var="""" {")
    $$$GENERATE($Char(9,9,9,9,9)_"Set $Piece(query,$$$NL,i) = ""-- ""_line")
    $$$GENERATE($Char(9,9,9,9)_"}")
    $$$GENERATE($Char(9,9,9)_"}")
    $$$GENERATE($Char(9,9)_"}")
    $$$GENERATE($Char(9,9)_"set tLines = 0 for tPtr = 1:1:$Length(query,$$$NL) { set tLine = $Piece(query,$$$NL,tPtr) if tLine '= """" { set tLines = tLines + 1, tLines(tLines) = tLine } }")
    // $$$GENERATE($Char(9,9)_"set sc=$$ExpandMacros^%SYS.DynamicQuery(%class,.tLines) Throw:$$$ISERR(sc) ##class(%Exception.StatusException).ThrowIfInterrupt(sc)")$$$GENERATE($Char(9,9)_"set SQLCODE = $$dynamic^%qaqpreparser(.tLines,.tStatementPreparsed,.tStatementArgs)")
    $$$GENERATE($Char(9,9)_"//")
    $$$GENERATE($Char(9,9)_"set tSelectMode = """_$Case($$$ucase(%parameter("SELECTMODE")), "RUNTIME": "", "ODBC": 1, "DISPLAY": 2, "LOGICAL": 0, : "")_"""")
    $$$GENERATE($Char(9,9)_"if SQLCODE=0 && ($Listlength(tStatementArgs) < 361) && ($Length(tStatementPreparsed) < 40000) {")
    $$$GENERATE($Char(9,9,9)_"set tExecuteArgs = """" for tPtr=1:2:$ListLength(tStatementArgs) { set tArg = $Case($List(tStatementArgs,tPtr),""?"":""$g(%parm(""_$Increment(qcount)_""))"",""c"":$$quoter^%qaqpreparser($List(tStatementArgs,tPtr+1)),""v"":""$g(""_$List(tStatementArgs,tPtr+1)_"")"",:"""") Set tExecuteArgs = tExecuteArgs _ "","" _ tArg }")
        $$$GENERATE($Char(9,9,9)_"set tSchemaPath = ##class(%SQL.Statement).%ClassPath($classname())")
        $$$GENERATE($Char(9,9,9)_"set tStatement = ##class(%SQL.Statement).%New(tSelectMode,tSchemaPath)")
        $$$GENERATE($Char(9,9,9)_"do tStatement.prepare(tStatementPreparsed)")
        $$$GENERATE($Char(9,9,9)_"Xecute ""set tResult = tStatement.%Execute(""_$Extract(tExecuteArgs,2,*)_"")""")
    $$$GENERATE($Char(9,9)_"}")
    $$$GENERATE($Char(9)_"}")
    $$$GENERATE($Char(9)_"catch tException { if '$Isobject($Get(tResult)) { set tResult = ##class(%SQL.StatementResult).%New() } set tResult.%SQLCODE=tException.AsSQLCODE(),tResult.%Message=tException.AsSQLMessage() }")
    $$$GENERATE($Char(9)_"Quit tResult")
    QUIT$$$OK
}

}
Rodrigo Werneck · Jul 18, 2023 go to post
Query FilterBy(
  Name As%String = "",
  Age As%Integer = "") As%SQLQuery(CONTAINID = 1, SELECTMODE = "RUNTIME") [ SqlName = SP_Sample_Filter_By, SqlProc ]
{
SELECT TOP 5 ID, Name, Age, SSN FROM Sample.Person
WHERE 
(nvl(:Name,'')='' or Name %STARTSWITH :Name)
AND
(nvl(:Age,'')='' or Age >= :Age)
}

This kind of query ends up preventing Caché SQL compiler from optimizing using index based on each of the criteria made optional.
That´s why I followed Paul´s idea and came up with %SQLQuery´s subclass SmartSQLQuery found above which dynamically comments out each criteria which is not applicable.

Rodrigo Werneck · Jul 24, 2023 go to post

You´re right, @Vitaliy Serdtsev 
In my test I had used a particular huge table of people with non-default mapping (legacy globals) and with a very specific and custom name index for which nvl(:Name,'') = '' inhibited the index.
But with this plain :Name IS NULL it worked fine.

Thanks a lot!

Rodrigo Werneck · Oct 25, 2023 go to post

I´ve got the same error when trying to compile the query and both tables are in the same namespace.
What else can be causing this?

Rodrigo Werneck · Oct 26, 2023 go to post

WRC has identified as a possible uintended limitation and filed a report with development (Jira DP-426592).

Rodrigo Werneck · Dec 18, 2023 go to post

@Enrico Parisi, I did no measures. I just thought that doing like @Julius Kavay  suggested should be more direct and more efficient. Perhaps his code takes more time because it runs in ObjectScript semi-interpreted code while internal methods like %ToJSON and %FromJSON seems to be in external C compiled code ($zu(210)?).
Thank you both,