Dim IsVersion11
Dim oDesktop
Dim oDesign
Dim oEditor
Dim oModule
Dim oAnsoftApp
Dim oProject
Dim oDefinitionManager
Dim Un,pi, IsCut, IsFast,iPort,IsPerfectConductor, RunTimeProjectName,NumPorts
Dim iShape,MainObj,InObj,ExObj,PostExObj,PostInObj,zStart,zEnd
Dim ProjectName,ProjectPath
Un="in": pi= 3.1415926535897932384626433832795
IsVersion11=true
call Main()
Sub Main()
	Dim NpassMin, NpassMax
	Dim dB_report,s_report
	Dim oShell, ofso
	Dim sDataFile, sDataDB, CutPlane,  ToSimulate
	zStart=0
    zEnd=0
'#######################################  GENERAL HFSS CONTROLS
	sDataFile="sTab.tab"         'EXPORTS Re/Im S-parameters
	sDataDB="SdB.tab"            'EXPORTS dB Magnitudes of s-parameters
	RunTimeProjectName="RunHFSS" 'HFSS PROJECT NAME (run time)
	ProjectName="FilterModel"    'HFSS PROJECT NAME (just model)
	ToSimulate=false             'TO RUN HFSS (true) or just DRAW MODEL (false)
	IsFast=true                  'FAST SWEEP (true) or INTERPOLATING (false)
	NpassMin=13                  'MIN NUMBER OF PASSES
	NpassMax=13                  'MAX NUMBER OF PASSES
'#######################################  DESIGN DATA CONTROLS FROM PROJECT FILE
	call ModelOpener()
'#######################################  DESIGN DATA CONTROLS FROM PROJECT FILE
	Dim Fc,F0,F1,Np,iSymX,iSymY
    DesignDatFile="project.dat"  'PROJECT FILE NAME
    rs = SplitProject(ProjectPath&DesignDatFile):  SetUpPart=rs(0): DesignPart=rs(1)
    set InDat = new SetUpDat:  call InDat.ImportFromText(SetUpPart)
    fc = InDat.fc                'SETUP FREQUENCY (GHz)
    f0 = InDat.f0                'SWEEP START FREQUENCY (GHz)
    f1 = InDat.f1                'SWEEP END FREQUENCY (GHz)
    Np = InDat.Np                '[NUMBER OF POINTS IN SWEEP]-1
    iUnit = InDat.IndUnit        'SIZE DIMENSIONS INDEX (0 if mm, 1 if inch)
    if iUnit=0 then Un="mm" else Un="in" end if
'#######################################  END CONTROLS
	NumPorts=2
    set design = New Struc
    call design.ImportFromText(DesignPart)
    iSymX=design.SymX: iSymY=design.SymY
	dB_report="dB":  s_report="sDat"
	call DrawFilter(ExObj,Design)
	call UniteElements()
	call SetSymmetry(iSymX,iSymY)
	Call SetBoundaries(iSymX,iSymY)
	Call SetPorts()
	call SetUp(NpassMin,NpassMax,0.02,Fc,F0,F1,Np)
	if not ToSimulate then exit sub
	Call AddReportDB(db_report)
	Call AddReport(s_report)
	call Simulate()
	call SaveReport(ProjectPath,"hfss.tab",dB_report)
	call SaveReport(ProjectPath,"sTab.tab",s_report)
	msgbox "Done"
End Sub
'#### DRAW FILTER ###################################################
Sub DrawFilter(ObjType,Design)
	Dim StepJunc
	Dim nJuncs,X0,Y0,X1,Y1,A,L,z,dB
	Dim W,T,H
	nJuncs = Design.Count
	z=zEnd
	Dim Nm, STATUS,i
	Dim iMin,iCount,iMax,nCount,Amin,Amax,Hmin,Hmax,Bmax
	for i=0 to nJuncs
		  	StepJunc=(Not Design.Juncs(i).IsNode) and (Design.Juncs(i).Index=1)
	        if Not StepJunc then 
				X0=Design.Juncs(i).X0
				X1=Design.Juncs(i).X1
				Y0=Design.Juncs(i).Y0
				Y1=Design.Juncs(i).Y1
				A=X1-X0: L=Design.Juncs(i).L
			end if
	next
	nCount=iCount
	for i=0 to nJuncs
		  	StepJunc=(Not Design.Juncs(i).IsNode) and (Design.Juncs(i).Index=1)
	        if Not StepJunc then 
				X0=Design.Juncs(i).X0
				X1=Design.Juncs(i).X1
				Y0=Design.Juncs(i).Y0
				Y1=Design.Juncs(i).Y1
				A=X1-X0: L=Design.Juncs(i).L
					iShape=iShape+1:Nm="obj"&iShape
					call DrawBox(STATUS,Nm,x0,y0,z,A,Y1-Y0,L)
	 				if STATUS then ObjType=ObjType&Nm&" "
	 			z=z+L
			end if
	next
	zEnd=z
End Sub
Sub SetSymmetry(iSymX,iSymY)
	if iSymX=1 or iSymX=-1 then
		call DrawCenterCut("YZ")
	end if
	if iSymY=1 or iSymY=-1 then
		call DrawCenterCut("ZX")
	end if
End Sub
Sub SetBoundaries(iSymX,iSymY)
	Dim iFace
	Set oModule = oDesign.GetModule("BoundarySetup")
	oModule.DeleteAllBoundaries
	if IsPerfectConductor then
		oModule.AssignPerfectE Array("NAME:PerfE0", "Objects:=", Array(MainObj), "InfGroundPlane:=", false)
	else
		oModule.AssignFiniteCond Array("NAME:FiniteCond1", "Objects:=", Array(MainObj), "UseMaterial:=",  _
		  false, "Conductivity:=", "58000000", "Permeability:=", "1", "UseThickness:=",  _
		  false, "Roughness:=", "0um", "InfGroundPlane:=", false)
	end if
	if iSymX=1 or iSymX=-1 then
		iFace=GetActiveFace(Array(0,0.01,0.01), MainObj)
		if iSymX=-1 then oModule.AssignPerfectH Array("NAME:PerfH1", "Faces:=", Array(iFace))
		if iSymX=1 then oModule.AssignPerfectE Array("NAME:PerfE1", "Faces:=", Array(iFace))
	end if
	if iSymY=1 or iSymY=-1 then
		iFace=GetActiveFace(Array(0.01,0.0,0.01), MainObj)
		if iSymY=-1 then oModule.AssignPerfectH Array("NAME:PerfH2", "Faces:=", Array(iFace))
		if iSymY=1 then oModule.AssignPerfectE Array("NAME:PerfE2", "Faces:=", Array(iFace))
	end if
End Sub
Sub SetPorts()
Dim i0,i1
i0=GetActiveFace(Array(0.01,0.01,zStart), MainObj)
i1=GetActiveFace(Array(0.01,0.01,zEnd), MainObj)
call PortsSetUp(Array(i0,i1))
End Sub
'########################### STRUC ################################
Class SetUpDat
    public IndUnit
    public ModesX
    public ModesY
    public IndFilter
    public Att
    public ResoNum
    public Bstrt
    public Bcntr
    public Bend
    public alfa
    public Fc
    public dF
    public f0
    public f1
    public Np
    public OptType
    public Nopt
    public dX
    public Wmin
    public Cmin
    public Nspec
    
    sub class_initialize()
    	IndUnit = 1
    	ModesX = 10
    	ModesY = 10
    	IndFilter = 1
    	Att = 0.05
    	ResoNum = 1
    	Bstrt = 1
    	Bcntr = 2
    	Bend = 1
    	alfa = 1.5
    	Fc = 12.5
    	dF = 1.5
    	f0 = 10
    	f1 = 15
    	Np = 200
    	OptType = 1
    	Nopt = 20
    	dX = 0.02
    	Wmin = 0.05
    	Cmin = 0.05
    end sub
    
    sub ImportFromText(InText)
        if trim(InText) ="" then exit sub
        InDatLines = split(InText,vbCrLf)
        n = ubound(InDatLines)
        if n > 4 then
           dim i, ii, iii
           ii = -1: iii = -1
           for i = 0 to n
            dim ShrtLine, vs
            ShrtLine = trim(InDatLines(i))
            if ShrtLine <>"" then
                ii = ii + 1
                vs = split(WordLineCorrect(" ",ShrtLine)," ")
                select case ii
                    case 0:
                        IndUnit = CInt(vs(0)): ModesX = CInt(vs(1))
                        ModesY = CInt(vs(2))
                    case 1:
                        IndFilter = CInt(vs(0)): Att = CDbl(vs(1))
                        ResoNum = CDbl(vs(2))
                        Bstrt = CDbl(vs(3)): Bcntr = CDbl(vs(4))
                        Bend = CDbl(vs(5))
                        alfa = CDbl(vs(6))
                    case 2:
                        Fc = CDbl(vs(0)): dF = CDbl(vs(1))
                    case 3:
                        f0 = CDbl(vs(0)): f1 = CDbl(vs(1)): Np = vs(2)
                    case 4:
                        OptType = CInt(vs(0)): Nopt = CInt(vs(1))
                        dX = CDbl(vs(2))
                        Wmin = CDbl(vs(3)): Cmin = CDbl(vs(4))
                end select
            end if
           next
        end if
   end sub
   
   function ExportToText()
    dim texto: texto = ""
    texto = texto & IndUnit & " " & ModesX & " " & ModesY & vbCrLf
    texto = texto & IndFilter & " " & Att & " " & ResoNum & " "
    texto = texto & Bstrt & " " & Bcntr & " " & Bend & " " & alfa & vbCrLf
    texto = texto & Fc & " " & dF & vbCrLf
    texto = texto & f0 & " " & f1 & " " & Np & vbCrLf
    ExportToText = texto
   end function
End class
Class STRUC
	Public ReferenceZ
	Public Wall
    Public Engine
    Public Eps, tg, sigm
    Public SymY, SymX, SymZ, Count
    Public AccessModes
    Public LocalModes
    Public PortModes
    Public Juncs
    Private Sub Class_Initialize
        ReDim Juncs(200)
        Count = -1
        SymY = 0 : SymX = 0 : SymZ = 0 : Eps = 1 : tg = 0 : sigm = 0
        AccessModes = "  1   1   1"
        LocalModes = "  1   10   10"
        PortModes = "  1    1"
        Engine = "Mu_WR"
        ReferenceZ=0.0
    End Sub
    Public Sub ImportFromText(StrucText)
        Engine = DefineEngine(StrucText)
        Dim CurrentJunc
        Dim LNs,vEnv
        LNs = Split(StrucText, vbCrLf)
        Select Case Engine
            Case "Mu_WR"
                If UBound(LNs) < 5 Then MsgBox("The schematic file is not complete") : Exit Sub
                vEnv = Split(WordLineCorrect(" ", Trim(LNs(0))), " ")
                SymX = CInt(vEnv(0))
                SymY = CInt(vEnv(1))
                SymZ = CInt(vEnv(2))
                AccessModes = LNs(1)
                LocalModes = LNs(2)
                PortModes = LNs(3)
                vEnv = Split(WordLineCorrect(" ", Trim(LNs(4))), " ")
                Eps = vEnv(0)
                tg = vEnv(1)
                sigm = vEnv(2)
            Case "C_WR"
                vEnv() = Split(WordLineCorrect(" ", Trim(LNs(0))), " ")
                SymY = vEnv(0)
                Eps = vEnv(1)
                tg = vEnv(2)
                sigm = vEnv(3)
        End Select
        Dim iElement, iCount
        iElement = -1
        For iCount = 1 To UBound(LNs)
            Set CurrentJunc = New ELEMENT
            CurrentJunc.Engine = Engine
            CurrentJunc.ImportFromText(LNs(iCount))
            If CurrentJunc.IsValid Then
                iElement = iElement + 1
                Set Juncs(iElement) = New ELEMENT
                Set Juncs(iElement) = CurrentJunc
            End If
        Next
        Count = iElement
    End Sub
    Public Function ExportToText()
        Dim rs
        rs = ""
        Select Case Engine
            Case "Mu_WR"
                rs = rs & "   " & SymX & "   " & SymY & "   " & SymZ & vbCrLf
                rs = rs & AccessModes & vbCrLf
                rs = rs & LocalModes & vbCrLf
                rs = rs & PortModes & vbCrLf
                rs = rs & "   " & NumOut(Eps, 3) & "   " & NumOut(tg, 5) & "   " & NumOut(sigm, 3) & vbCrLf
            Case "C_WR"
                rs = "   " & SymY & "   " & NumOut(Eps, 3) & "   " & NumOut(tg, 5) & "   " & NumOut(sigm, 3) & vbCrLf
        End Select
        For iCount = 0 To Count
            rs = rs & Juncs(iCount).ExportToText & vbCrLf
        Next
        ExportToText = rs
    End Function
    Public Function Length()
        Dim zL
        zL=0.0
        For iCount = 0 To Count
            With Juncs(iCount)
                If .IsDrawable Then
                    zL = zL & FormatNumber(.L, 5)
                End If
            End With
        Next
        zL = FormatNumber(zL, 5)
        Length= zL
    End Function
    Private Function DefineEngine(StrucDat)
        DefineEngine = "UNKNOWN"
        Dim StrucLN,nStruc0,nStruc1
        StrucLN= Split(StrucDat, vbCrLf)
        nStruc0 = nVars(StrucLN(0))
        nStruc1 = nVars(StrucLN(1))
        If nStruc0 = 2 And nStruc1 = 2 Then DefineEngine = "Mu_WR"
        If nStruc0 = 3 And nStruc1 = 6 Then DefineEngine = "C_WR"
    End Function
    Private Function nVars(LN)
        Dim v0
        v0 = Split(WordLineCorrect(" ", Trim(LN)), " ")
        nVars= UBound(v0)
    End Function
End Class
Class ELEMENT
    Public Engine 
    Public X0 
    Public Y0 
    Public X1 
    Public Y1 
    Public L 
    Public Mark 
    Public Index 
    Public IsNode
    Public Note 
    Public IsValid
    
    Private Sub Class_Initialize
        Engine = "C_WR"
        X0 = 0 : X1 = 0 : Y0 = 0 : Y1 = 0 : L = 0 : Mark = "0" : Index = 0 : IsNode = True : Note = ""
        IsValid = False
    End Sub
    Public Sub ImportFromText(StrucText)
        Dim sVars
        sVars = StrucText
        If Trim(StrucText) = "" Then IsValid = False : Exit Sub
        If Left(StrucText, 1) = " " Then sVars = RTrim("0" & sVars)
        Dim v
        v = Split(WordLineCorrect(" ", StrucText), " ")
        If UBound(v) < 6 Then IsValid = False : Exit Sub
        If UBound(v) > 6 Then IsNode = False Else IsNode = True
        Mark = v(0)
        Index = CInt(v(1))
        L = CDbl(v(2))
        Select Case Engine
            Case "C_WR"
                X0 = -CDbl(v(3))
                X1 = CDbl(v(3))
                Y0 = CDbl(v(5))
                Y1 = Y0 + CDbl(v(4))
            Case "Mu_WR"
                X0 = CDbl(v(3))
                Y0 = CDbl(v(4))
                X1 = CDbl(v(5))
                Y1 = CDbl(v(6))
        End Select
        IsValid = True
    End Sub
    Public Function ExportToText()
        Dim rs, A, B,H
        rs = ""
        Select Case Engine
            Case "C_WR"
                A = (X1 - X0) / 2
                B = Y1 - Y0
                H = Y0
                rs = Mark & "   " & Index & "   " & NumOut(L, 5)
                rs = rs & "   " & NumOut(A, 5) & "   " & NumOut(B, 5) & "   " & NumOut(H, 5) & "   0.00000"
            Case "Mu_WR"
                rs = Mark & "   " & Index & "   " & NumOut(L, 5)
                rs = rs & "   " & NumOut(X0, 5) & "   " & NumOut(Y0, 5) & "   " & NumOut(X1, 5) & "   " & NumOut(Y1, 5)
        End Select
        If Not IsNode Then rs = rs & "   0.00000"
        ExportToText = rs
    End Function
    Public Function IsDrawable()
    	Dim A,B
        IsDrawable = False
        A = (X1 - X0) / 2
        B = Y1 - Y0
        If IsValid Then
            If IsNode Then
                If Index = 1 Then
                    If A <> 0 And B <> 0 And L <> 0 Then IsDrawable = True
                End If
            Else
                If Index = 2 Or Index = 5 Then
                    If A <> 0 And B <> 0 And L <> 0 Then IsDrawable = True
                End If
            End If
        End If
    End Function
End Class
'##########   HFSS      ##############################################
Sub UniteElements()
	ExObj=Trim(ExObj):InObj=trim(InObj)
	if ExObj="" then exit sub
	ExObj=replace(ExObj," ",",")
	MainObj=TheMainObj(ExObj)
	call DrawUnite(ExObj)
	if InObj<>"" then
	InObj=replace(InObj," ",",")
	call DrawSubtract(MainObj,InObj)
	if Trim(PostExObj)<>"" then PostExObj=MainObj&","&replace(Trim(PostExObj)," ",","): call DrawUnite(PostExObj)
	if Trim(PostInObj)<>"" then PostInObj=replace(Trim(PostInObj)," ",","): call DrawSubtract(MainObj,PostInObj)
	end if
End Sub
Function TheMainObj(Obj)
Dim xu
xu=split(Obj,",")
if ubound(xu)>=0 then TheMainObj=xu(0) else  TheMainObj=""
End Function
'############# HFSS MATERIALS ###########################
Sub AddMaterial(Nm,eps,tg)
	if IsVersion11 then
		Set oDefinitionManager = oProject.GetDefinitionManager()
		oDefinitionManager.AddMaterial Array("NAME:"&Nm, "CoordinateSystemType:=",  _
		  "Cartesian", Array("NAME:AttachedData"), Array("NAME:ModifierData"), "permittivity:=",  _
		  eps, "dielectric_loss_tangent:=", tg)
		else
		oProject.AddMaterial Array("NAME:"&Nm, "permittivity:=", eps, "dielectric_loss_tangent:=",  _
	  tg)
	end if
End Sub
Sub SetMaterial(NmObj,NmMaterial,SolveInside)
	if IsVersion11 then
		oEditor.AssignMaterial Array("NAME:Selections", "Selections:=", NmObj), Array("NAME:Attributes", "MaterialValue:=",  _
	 	 "" & Chr(34) & NmMaterial & Chr(34) & "", "SolveInside:=", SolveInside)
 	 else
		oEditor.AssignMaterial Array("NAME:Selections", "Selections:=", NmObj), Array("NAME:Attributes", "MaterialName:=",  _
	  NmMaterial, "SolveInside:=", SolveInside)
	end if
End Sub
'#############HFSS DRAW ###################################
Sub DrawCenterCut(Plane)
	oEditor.Split Array("NAME:Selections", "Selections:=", MainObj), Array("NAME:SplitToParameters", "CoordinateSystemID:=",  _
	  -1, "SplitPlane:=", Plane, "WhichSide:=", "PositiveOnly", "SplitCrossingObjectsOnly:=",  _
	  false)
End Sub
Sub DrawBox(STATUS,Nm,x,y,z,dx,dy,dz)
STATUS=TRUE
if abs(CDbl(dx))<0.0001 or abs(CDbl(dy))<0.0001  or abs(CDbl(dz))<0.0001 then STATUS=False: exit sub
oEditor.CreateBox Array("NAME:BoxParameters", "CoordinateSystemID:=", -1, "XPosition:=",  _
  v(x), "YPosition:=", v(y), "ZPosition:=", v(z), "XSize:=", v(dx), "YSize:=",  _
  v(dy), "ZSize:=", v(dz)), Array("NAME:Attributes", "Name:=", Nm, "Flags:=",  _
  "", "Color:=", "(132 132 193)", "Transparency:=", 0, "PartCoordinateSystem:=",  _
  "Global", "MaterialName:=", "vacuum", "SolveInside:=", true)
End Sub
Sub DrawUnite(NmObj)
if ubound(split(NmObj,","))<=0 then exit sub
oEditor.Unite Array("NAME:Selections", "Selections:=", NmObj), Array("NAME:UniteParameters", "CoordinateSystemID:=",  _
  -1, "KeepOriginals:=", false)
End Sub
Sub DrawSubtract(NmObj0,nmObj)
oEditor.Subtract Array("NAME:Selections", "Blank Parts:=", NmObj0, "Tool Parts:=",  _
  NmObj), Array("NAME:SubtractParameters", "CoordinateSystemID:=", -1, "KeepOriginals:=",  _
  false)
End Sub
function v(x)
if x=Empty then v="0in" else v=x&Un end if
end function
Sub PortsSetUp(Faces)
	
Dim nCount,nBound, NumPorts
nBound=ubound(Faces)
NumPorts=nBound
for nCount=0 to nBound
oModule.AssignWavePort Array("NAME:WavePort"&(nCount+1), "Faces:=", Array(CInt(Faces(nCount))), "NumModes:=", 1, "PolarizeEField:=",  _
  false, "DoDeembed:=", false, Array("NAME:Modes", Array("NAME:Mode1", "ModeNum:=", 1, "UseIntLine:=",  _
  false)))
next
End Sub
Public Function GetActiveFace(x, objName)
        Dim hren
        hren=Array("NAME:Parameters", "BodyName:=", objName, "XPosition:=", x(0)&Un, "YPosition:=", x(1)&Un, "ZPosition:=", x(2)&Un)
        GetActiveFace= oEditor.GetFaceByPosition(hren)
End Function
'############  HFSS REPORTS  ########################
Sub SetUp(NpassMin,NpassMax,ErrMax,Fc,F0,F1,Np)
if IsVersion11 then
	Set oModule = oDesign.GetModule("AnalysisSetup")
	oModule.InsertSetup "HfssDriven", Array("NAME:Setup1", "Frequency:=", Fc&"GHz", "PortsOnly:=",  _
  false, "MaxDeltaS:=", ErrMax, "UseMatrixConv:=", false, "MaximumPasses:=", NpassMax, "MinimumPasses:=",  _
  NpassMin, "MinimumConvergedPasses:=", 1, "PercentRefinement:=", 30, "BasisOrder:=",  _
  1, "UseIterativeSolver:=", false, "DoLambdaRefine:=", true, "DoMaterialLambda:=",  _
  true, "SetLambdaTarget:=", false, "Target:=", 0.3333, "UseConvOutputVariable:=",  _
  false, "IsEnabled:=", true, "ExternalMesh:=", false, "UseMaxTetIncrease:=",  _
  false, "MaxTetIncrease:=", 100000, "PortAccuracy:=", 2, "UseABCOnPort:=",  _
  false, "SetPortMinMaxTri:=", false)
	  	if IsFast then
			oModule.InsertFrequencySweep "Setup1", Array("NAME:Sweep", "IsEnabled:=", true, "SetupType:=",  _
		  "LinearCount", "StartValue:=", F0&"GHz", "StopValue:=", F1&"GHz", "Count:=",  _
		  Np+1, "Type:=", "Fast", "SaveFields:=", true, "ExtrapToDC:=", false)
	  	else
oModule.InsertFrequencySweep "Setup1", Array("NAME:Sweep", "IsEnabled:=", true, "SetupType:=",  _
  "LinearCount", "StartValue:=", F0&"GHz", "StopValue:=", F1&"GHz", "Count:=",  _
  Np+1, "Type:=", "Interpolating", "SaveFields:=", false, "SaveRadFields:=",  _
  false, "InterpTolerance:=", 0.5, "InterpMaxSolns:=", 250, "InterpMinSolns:=",  _
  0, "InterpMinSubranges:=", 1, "ExtrapToDC:=", false, "InterpUseS:=", true, "InterpUsePortImped:=",  _
  false, "InterpUsePropConst:=", true, "UseDerivativeConvergence:=", false, "InterpDerivTolerance:=",  _
  0.2, "UseFullBasis:=", true, "EnforcePassivity:=", false)
	  	end if
  else
  Set oModule = oDesign.GetModule("AnalysisSetup")
  oModule.InsertSetup "HfssDriven", Array("NAME:Setup1", "Frequency:=", Fc&"GHz", "PortsOnly:=",  _
  false, "MaxDeltaS:=", 0.02, "UseMatrixConv:=", false, "MaximumPasses:=",NpassMax, "MinimumPasses:=",  _
  NpassMin, "MinimumConvergedPasses:=", 1, "PercentRefinement:=", 20, "ReducedSolutionBasis:=",  _
  false, "DoLambdaRefine:=", true, "DoMaterialLambda:=", true, "Target:=",  _
  0.3333, "PortAccuracy:=", 2, "SetPortMinMaxTri:=", false)
oModule.InsertDrivenSweep "Setup1", Array("NAME:Sweep", "Type:=", "Interpolating", "InterpTolerance:=",  _
  0.5, "InterpMaxSolns:=", 20, "SetupType:=", "LinearCount", "StartFreq:=",  _
  F0&"GHz", "StopFreq:=", F1&"GHz", "Count:=", Np+1, "SaveFields:=", false, "ExtrapToDC:=",  _
  false)
  end if
End Sub
Sub Simulate()
	
oProject.Save
If IsVersion11 then
oDesign.AnalyzeAll
else
oDesign.Solve Array("Setup1")
end if
End Sub
Sub AddReportDB(DataTableName)
	
Dim i,j,Path,S_Path
	Set oModule = oDesign.GetModule("ReportSetup")
Path=""
for i=1 to NumPorts+1
for j=1 to NumPorts+1
Path=Path&"dB(S(WavePort"&i&",WavePort"&j&"))"&" "
next
next
S_Path=split(Trim(Path)," ")
	oModule.CreateReport DataTableName, "Modal Solution Data", "Data Table",  _
  "Setup1 : Sweep", Array("Domain:=", "Sweep"), Array("Freq:=", Array("All")), Array("X Component:=",  _
  "Freq", "Y Component:=", S_Path), Array()
oModule.ChangeProperty Array("NAME:AllTabs", Array("NAME:Data Filter", Array("NAME:PropServers",  _
  DataTableName&":PrimarySweepDrawing"), Array("NAME:ChangedProps", Array("NAME:Units", "Value:=",  _
  "GHz"))))
End Sub
Sub AddReport(DataTableName)
Dim S_Path,i,j,nArray,Path
Path=""
	for i=1 to NumPorts+1
	for j=1 to NumPorts+1
	Path=Path&"re(S(WavePort"&i&",WavePort"&j&"))"&" "&"im(S(WavePort"&i&",WavePort"&j&"))"&" "
	next
	next
S_Path=split(Trim(Path)," ")
Set oModule = oDesign.GetModule("ReportSetup")
oModule.CreateReport DataTableName, "Modal Solution Data", "Data Table",  _
  "Setup1 : Sweep", Array("Domain:=", "Sweep"), Array("Freq:=", Array("All")), Array("X Component:=",  _
  "Freq", "Y Component:=", S_Path), Array()
Set oModule = oDesign.GetModule("ReportSetup")
oModule.CreateReport "Data Table 1", "Modal Solution Data", "Data Table",  _
  "Setup1 : Sweep", Array("Domain:=", "Sweep"), Array("Freq:=", Array("All")), Array("X Component:=",  _
  "Freq", "Y Component:=", Array("dB(S(WavePort1,WavePort1))",  _
  "dB(S(WavePort1,WavePort2))", "dB(S(WavePort1,WavePort3))",  _
  "dB(S(WavePort2,WavePort1))")), Array()
 
End Sub
Sub SaveReport(s_FilePath,s_FileName,DataTableName)
oModule.ExportToFile DataTableName, s_FilePath & s_FileName
End Sub
Sub ModelOpener()
        set oAnsoftApp = CreateObject("AnsoftHfss.HfssScriptInterface")
        set oDesktop = oAnsoftApp.GetAppDesktop()
        set oProject = oDesktop.GetActiveProject
        ProjectName=oProject.GetName()
        ProjectPath=oProject.GetPath()
        	Dim DesktopProjects
        	DesktopProjects = oDesktop.GetProjectList
        	Dim nProject ,i
        	nProject = UBound(DesktopProjects)
        	For i  = 0 To nProject
            	if UCASE(DesktopProjects(i))<>UCASE(RunTimeProjectName) then oDesktop.CloseProject(DesktopProjects(i))
        	Next
        oDesktop.NewProject
        set oProject = oDesktop.GetActiveProject
        oProject.InsertDesign "HFSS","HFSSModel1","DrivenModal",""
        set oDesign = oProject.SetActiveDesign("HFSSModel1")
        set oEditor = oDesign.SetActiveEditor("3D Modeler")
        Dim Arr
        Arr=Array("NAME:Units Parameter", "Units:=", Un, "Rescale:=", False)
        oEditor.SetModelUnits(Arr)
        
        Dim Version
        On Error Resume Next
        Version = Trim(oDesktop.GetVersion())
        if Err.Number <> 0 then
            Version = "9.0"
            IsVersion11=false
        	Call oProject.SaveAs(ProjectPath&ProjectName&".hfss", True)
        else
            dim vars
            vars=split(version,".")
       		if CInt(vars(0))<2015 then
        		Call oProject.SaveAs(ProjectPath&ProjectName&".hfss", True)
        	else
        		Call oProject.SaveAs(ProjectPath&ProjectName&".aedt", True)
        	end if
            IsVersion11=true
        end if
End Sub
'##########   GENERAL   ##############################################
sub OpenFile(FiloName, TextInside)
Dim fso, f
Set fso=CreateObject("Scripting.FileSystemObject")
if fso.FileExists(FiloName) then
Set f=fso.OpenTextFile(FiloName, 1)
TextInside=ltrim(rtrim(f.ReadAll))
f.Close
Set f=Nothing
else
TextInside=""
end if
Set fs=Nothing
end sub
Function WordLineCorrect(Median,TextLine)
dim VV,Nvv,iv,icount,N,InMark,i,r,dLine,A
N=len(TextLine)
InMark=True
for i=1 to N
r=mid(TextLine,i,1)
if r=chr(9) then r=" "
dLine=r
if InMark and r=" " then dLine="" end if
if r=" " then InMark=True else InMark=False end if
A=A&dLine
next
if Median =" " then 
WordLineCorrect=trim(A)
else
WordLineCorrect=replace(trim(A)," ",Median)
end if
end function
Sub GetCurrentLocation()
	Dim oShell, ofso
	Set oShell = CreateObject("WScript.Shell")
	Set ofso = CreateObject("Scripting.FileSystemObject")
	oShell.CurrentDirectory = oFSO.GetParentFolderName(Wscript.ScriptFullName)
	ProjectPath=oShell.CurrentDirectory&"\"  'Transition A7 data file
	Set oShell=Nothing
	Set ofso = Nothing
End Sub
function SplitProject(DesignDatFile)
    call OpenFile(DesignDatFile, txt)
    dim SetupDat, DesignDat, kod
    SetupDat="": DesignDat="": kod = -1
    if trim(txt)="" then
         msgbox "The project file is empty"
    end if
    txt=replace(txt,vbCrLf,vbLf)
    LNs = split(txt,vbLf): N=ubound(LNs)
    for i=0 to N
        LN=trim(LNs(i))
        if len(LN)>3 then
            key = ucase(left(LN,4))
            if key = "SETU" then kod = 1
            if key = "DESI" then kod = 2
            if kod = 1 and key <> "SETU" then SetupDat =SetupDat & LNs(i) & vbCrLf
            if kod = 2 and key <> "DESI" then DesignDat =DesignDat & LNs(i) & vbCrLf
        end if
    next    
    if kod>0 then
        if trim(SetupDat)="" then msgbox "No setup data found in project file": end if
        if trim(DesignDat)="" then msgbox "No design data found in project file": end if
        SplitProject=Array(SetupDat,DesignDat)
    else
        msgbox "Wrong data records in project file"
    end if
End function