Método de operación y código fuente de la herramienta de búsqueda del diccionario coreano/inglés de Naver

Se explican el método de operación y el código fuente de la herramienta de búsqueda del diccionario coreano/diccionario inglés de Naver.

Esta es una continuación del artículo anterior.

Descripción general de la herramienta de búsqueda del diccionario Naver Korean Dictionary/English Dictionary

1. Método de funcionamiento y precauciones de la herramienta de búsqueda del diccionario coreano Naver/diccionario inglés

Un usuario realiza una solicitud de búsqueda al servicio de Naver utilizando un navegador web y el servidor de Naver responde con un resultado de procesamiento de la solicitud.

(Para obtener más información sobre cómo funciona la web, lea el artículo de resultados de búsqueda de Google a continuación).
https://www.google.co.kr/search?q=web+action+method

Echemos un vistazo más de cerca a la solicitud de búsqueda y la respuesta del servicio de diccionario de Naver.

1.1. Solicitud y respuesta de búsqueda en el diccionario Naver

Hay varias formas de verificar los contenidos intercambiados con el servidor a través de un navegador web, y aquí explicaremos cómo usar Fiddler Web Debugger.

El siguiente es el resultado de verificar el contenido de la solicitud y la respuesta en Fiddler al buscar la palabra "registrarse" en el diccionario coreano de Naver.

Fiddler로 살펴본 네이버 사전 검색 요청과 응답
Solicitud y respuesta de búsqueda en el diccionario Naver con Fiddler
  1. URL, tipo de contenido: puede consultar el contenido a continuación.
    • Protocolo: HTTPS
    • Anfitrión: es.dict.naver.com
    • URL: /api3/koko/search?query=%EA%B0%80%EC%9E%85&m=pc&hid=162470754628591300
      • 여기에서 “%EA%B0%80%EC%9E%85″는 “가입”이 URL Encoding된 문자열이다.
  2. Encabezado de solicitud
    • Se puede comprobar User-Agent, Cookie, etc.
  3. Contenido de la respuesta
    • Tipo de contenido: application/json;charset=UTF-8
      • Puede ver que el contenido de la respuesta está en formato json y el juego de caracteres está codificado en UTF-8.
    • Longitud del contenido: 50814
      • Se puede observar que el contenido de la respuesta es de 50.814 bytes, aproximadamente 50KB.
    • Cuerpo del contenido: {“searchResultMap”:{“searchResultListMap”:{“WORD”:{“query”:”Unirse”, …
      • Es una cadena JSON, y si la marca en la pestaña "JSON", tiene una estructura jerárquica de la siguiente manera.
네이버 국어사전 HTTP Response JSON 구조
Estructura JSON de respuesta HTTP del diccionario coreano NAVER

1.2. Cambiar el formato del resultado de la respuesta (HTML -> JSON)

Esta herramienta no utiliza la API abierta de Naver, pero utiliza métodos de solicitud y respuesta web.

Aunque no es exacto, el formato de los resultados de las respuestas cambió alrededor de diciembre de 2018. Antes de eso, estaba en formato HTML, pero en este momento, cuando lo verifiqué accidentalmente con Fiddler, descubrí que la respuesta se cambió al formato JSON.

La primera versión de esta herramienta se creó cuando la respuesta estaba en formato HTML. Extraje los elementos necesarios de HTML, pero cada vez que Naver cambiaba la estructura HTML, no funcionaba correctamente, por lo que tenía que cambiar el código fuente cada vez para que coincidiera con la estructura HTML modificada. Dado que el formato del resultado de la respuesta se cambió a JSON, funciona bien sin cambiar el código fuente.

1.3. Precauciones de uso

No es posible confirmar si Naver ha anunciado oficialmente que proporciona resultados de búsqueda de diccionarios en formato JSON. La documentación de la estructura de JSON también parece no estar publicada.
(Si se han publicado noticias o datos, háganoslo saber en los comentarios).

Por esta razón, es posible que de repente no funcione algún día, así que tenga cuidado.

2. Implementación

2.1. Resumen de flujo general

Codifique en URL la palabra que se buscará y ejecute la función GetDataFromURL para analizar el resultado de la búsqueda JSON obtenido para extraer los elementos necesarios.

Dim aWord As String, sBaseURL As String, sWord As String
aWord = "가입"
sBaseURL = "https://ko.dict.naver.com/api3/koko/search?query=%s" '기본 URL
sWord = URLEncodeUTF8(aWord) '검색어 URL Encoding

Dim sURL As String, sURLData As String, oParsedDic As Dictionary
sURL = Replace(sBaseURL, "%s", sWord) '기본 URL에 검색어 대입
sURLData = GetDataFromURL(sURL, "GET", "", "utf-8") 'URL에서 결과 가져오기
Set oParsedDic = JsonConverter.ParseJson(sURLData) 'JSON결과를 Dictionary로 변환

'JSON이 변환된 Dictionary에서 검색결과에 해당하는 항목 추출
'시작 Path: oParsedDic("searchResultMap")("searchResultListMap")("WORD")("items")

Echemos un vistazo a las funciones principales.

2.2. Codificación de URL (código fuente URLEncodeUTF8)

Devuelve la URL de la solicitud de búsqueda como una cadena URLEncoded. Se utiliza la clase ADODB.Stream.

Public Function URLEncodeUTF8( _
   StringVal As String, _
   Optional SpaceAsPlus As Boolean = False _
) As String
  Dim bytes() As Byte, b As Byte, i As Integer, space As String

  If SpaceAsPlus Then space = "+" Else space = "%20"

  If Len(StringVal) > 0 Then
    With New ADODB.Stream
      .Mode = adModeReadWrite
      .Type = adTypeText
      .CharSet = "UTF-8"
      .Open
      .WriteText StringVal
      .Position = 0
      .Type = adTypeBinary
      .Position = 3 ' skip BOM
      bytes = .Read
    End With

    ReDim Result(UBound(bytes)) As String

    For i = UBound(bytes) To 0 Step -1
      b = bytes(i)
      Select Case b
        Case 97 To 122, 65 To 90, 48 To 57, 45, 46, 95, 126
          Result(i) = Chr(b)
        Case 32
          Result(i) = space
        Case 0 To 15
          Result(i) = "%0" & Hex(b)
        Case Else
          Result(i) = "%" & Hex(b)
      End Select
    Next i

    URLEncodeUTF8 = Join(Result, "")
  End If
End Function

Para usar la biblioteca ADODB, se debe hacer referencia a la "Biblioteca Microsoft ActiveX Data Object 6.1". en la pantalla de excel alternativa + F11 Simplemente presione la tecla y cambie al Editor de VBA para agregarlo.

엑셀 VBA 라이브러리 참조 추가
Agregue la referencia de la biblioteca Excel VBA


2.3. Solicitar y obtener respuesta (código fuente de la función GetDataFromURL)

Use la clase "WinHttp.WinHttpRequest" para establecer el encabezado de la solicitud y la información de la opción, visitar la URL de búsqueda y obtener el resultado. Dado que es un método de enlace tardío que crea objetos con CreateObject, no es necesario agregar una referencia de biblioteca.

Function GetDataFromURL(strURL, strMethod, strPostData, Optional strCharSet = "UTF-8")
  Dim lngTimeout
  Dim strUserAgentString
  Dim intSslErrorIgnoreFlags
  Dim blnEnableRedirects
  Dim blnEnableHttpsToHttpRedirects
  Dim strHostOverride
  Dim strLogin
  Dim strPassword
  Dim strResponseText
  Dim objWinHttp
  lngTimeout = 59000
  strUserAgentString = "http_requester/0.1"
  intSslErrorIgnoreFlags = 13056 ' 13056: ignore all err, 0: accept no err
  blnEnableRedirects = True
  blnEnableHttpsToHttpRedirects = True
  strHostOverride = ""
  strLogin = ""
  strPassword = ""
  Set objWinHttp = CreateObject("WinHttp.WinHttpRequest.5.1")
  '--------------------------------------------------------------------
  'objWinHttp.SetProxy 2, "xxx.xxx.xxx.xxx:xxxx", "" 'Proxy를 사용하는 환경에서 설정
  '--------------------------------------------------------------------
  objWinHttp.SetTimeouts lngTimeout, lngTimeout, lngTimeout, lngTimeout
  objWinHttp.Open strMethod, strURL
  If strMethod = "POST" Then
    objWinHttp.SetRequestHeader "Content-type", "application/x-www-form-urlencoded; charset=UTF-8"
  Else
    objWinHttp.SetRequestHeader "Content-type", "text/html; charset=euc-kr"
  End If
  If strHostOverride <> "" Then
    objWinHttp.SetRequestHeader "Host", strHostOverride
  End If

  objWinHttp.Option(0) = strUserAgentString
  objWinHttp.Option(4) = intSslErrorIgnoreFlags
  objWinHttp.Option(6) = blnEnableRedirects
  objWinHttp.Option(12) = blnEnableHttpsToHttpRedirects
  If (strLogin <> "") And (strPassword <> "") Then
    objWinHttp.SetCredentials strLogin, strPassword, 0
  End If
  On Error Resume Next
  objWinHttp.Send (strPostData)
  objWinHttp.WaitForResponse
  If Err.Number = 0 Then
    If objWinHttp.Status = "200" Then
      'GetDataFromURL = objWinHttp.ResponseText
      GetDataFromURL = BinaryToText(objWinHttp.ResponseBody, strCharSet)
    Else
      GetDataFromURL = "HTTP " & objWinHttp.Status & " " & _
        objWinHttp.StatusText
    End If
  Else
    GetDataFromURL = "Error " & Err.Number & " " & Err.Source & " " & _
      Err.Description
  End If
  On Error GoTo 0
  Set objWinHttp = Nothing
End Function

2.4. Respuesta (resultado de búsqueda) Cadena JSON

La cadena JSON de respuesta (resultado de búsqueda) contiene bastante información. Es difícil de ver porque no hay sangría ni separación de líneas. (extractos parciales)

{ &quot;searchResultMap&quot;: { &quot;searchResultListMap&quot;: { &quot;WORD&quot;: { &quot;query&quot;: &quot;Unirse&quot;, &quot;queryRevert&quot;: &quot;&quot;, &quot;items&quot;: [ { &quot;rank&quot;: &quot;1&quot;, &quot;gdid&quot;: &quot; 8800000f_4002c436c93d4bb38d3e58632fe00af0&quot;, &quot;matchType&quot;: &quot;exact:entry&quot;, &quot;entryId&quot;: &quot;4002c436c93d4bb38d3e58632fe00af0&quot;, &quot;serviceCode&quot;: &quot;1&quot;, &quot;languageCode&quot;: &quot;KOKO&quot;, &quot;expTypeDictTypeForm&quot;: &quot;word&quot;, &quot;dict 2&quot;, &quot;sourceDictnameKO&quot;: &quot;Diccionario estándar de coreano&quot;, &quot;sourceDictnameOri&quot;: &quot;Diccionario estándar de coreano.&quot;, &quot;sourceDictnameLink&quot;: &quot;https://stdict.korean.go.kr/main/main.do&quot;, .. .&quot;expEntry &quot;: &quot;<strong>entrar</strong>&quot;, ... &quot;destinationLink&quot;: &quot;#/entry/koko/4002c436c93d4bb38d3e58632fe00af0&quot;, ... &quot;meansCollector&quot;: [ { &quot;partOfSpeech&quot;: &quot;sustantivo&quot;, &quot;partOfSpeech2&quot;: &quot;sustantivo&quot;, &quot;significa&quot;: [ { &quot;order&quot;: &quot;1&quot;, &quot;value&quot;: &quot;Solicitud de un producto para unirse a una organización u organización o para proporcionar un servicio.&quot;, ... &quot;exampleOri&quot;: &quot;<strong>entrar</strong> Formulario de solicitud.&quot;, ... }, { &quot;order&quot;: &quot;2&quot;, &quot;value&quot;: &quot;Recién insertado&quot;., ... &quot;exampleOri&quot;: &quot;Cualquier corrección hecha en medio del manuscrito <strong>entrar</strong>ha sido encontrado.&quot;, ... }, { &quot;orden&quot;: &quot;3&quot;, &quot;valor&quot;: &quot;Actos obligados por el tratado sin certificación del texto. Comunidad legal al permitir que las partes se conviertan en partes solo por expresión de intención...&quot;, ... &quot;languageGroup&quot;: &quot;Law&quot;, ... &quot;exampleTrans&quot;: null, ... } ] } ], &quot;similarWordList&quot;: []. &quot;加入&quot; } ], ... }, { &quot;rango&quot;: &quot;2&quot;, &quot;gdid&quot;: &quot;881857e6_e12c4e3432cf458c929bd49c929fd80b&quot;, &quot;matchType&quot;: &quot;exacta:entrada&quot;, &quot;entryId&quot;: &quot;e12c4e3432cf458c929bd49c929fd80b&quot;, &quot;serviceCode&quot;: &quot;serviceCode&quot;: &quot;1&quot;, &quot;languageCode&quot;: &quot;KOKO&quot;, &quot;expDictTypeForm&quot;: &quot;Word&quot;, &quot;dictTypeForm&quot;: &quot;2&quot;, &quot;sourceDictnameKO&quot;: &quot;Urimalsaem&quot;, &quot;sourceDictnameOri&quot;: &quot;Urimalsaem&quot;, &quot;sourceDictnameLink&quot;: &quot;https : //opendict.korean.go.kr/main&quot;, ... &quot;expEntry&quot;: &quot;<strong>entrar</strong>&quot;, ... &quot;destinationLink&quot;: &quot;#/entry/koko/e12c4e3432cf458c929bd49c929fd80b&quot;, ... &quot;meansCollector&quot;: [ { &quot;partOfSpeech&quot;: &quot;sustantivo&quot;, &quot;partOfSpeech2&quot;: &quot;sustantivo&quot;, &quot;significa&quot;: [ { &quot;order&quot;: &quot;&quot;, &quot;value&quot;: &quot;La adición de un nuevo individuo a una población. Sin embargo, solo se aplican los objetos que han alcanzado una cierta etapa de desarrollo.&quot;, ... } ] } ], &quot;similarWordList&quot;: [], &quot;antonymWordList&quot;: [], ... }, ], &quot;total&quot;: 96, &quot;tipo de sección&quot;: &quot;PALABRA&quot;, &quot;revertir&quot;: &quot;&quot;, &quot;orKEquery&quot;: nulo } } } }


2.5. analizador JSON

Puede extraer el elemento deseado de la cadena JSON mediante funciones de cadena (MID, INSTR, etc.), pero la búsqueda es complicada y el código se vuelve muy desordenado.

Si se implementa en Python, simplemente importe el módulo json y use la clase json. No hay muchas bibliotecas abiertas para VBA, pero afortunadamente hay un analizador JSON publicado en github, así que lo usé bien.

https://github.com/VBA-tools/VBA-JSON

El código fuente de este analizador JSON tiene 1123 líneas, por lo que no se publica en el blog. Si lo necesita, verifique el código fuente en la URL anterior. Un ejemplo simple que usa el analizador JSON es el siguiente (código publicado en github arriba):

Dim Json As Object
Set Json = JsonConverter.ParseJson("{""a"":123,""b"":[1,2,3,4],""c"":{""d"":456}}")

' Json("a") -> 123
' Json("b")(2) -> 2
' Json("c")("d") -> 456
Json("c")("e") = 789

Debug.Print JsonConverter.ConvertToJson(Json)
' -> "{"a":123,"b":[1,2,3,4],"c":{"d":456,"e":789}}"

Debug.Print JsonConverter.ConvertToJson(Json, Whitespace:=2)
' -> "{
'       "a": 123,
'       "b": [
'         1,
'         2,
'         3,
'         4
'       ],
'       "c": {
'         "d": 456,
'         "e": 789  
'       }
'     }"

2.6. Botón de búsqueda, haga clic en el código fuente del evento

Este código se ejecuta cuando se hace clic en el botón "Búsqueda en el diccionario de Naver" en la hoja "Búsqueda en el diccionario". Se implementa lo siguiente:

  • Compruebe si las opciones están configuradas correctamente.
  • Una búsqueda en el diccionario se ejecuta repetidamente para un término de búsqueda y el resultado se muestra en una hoja.
    • Los resultados mostrados son tipo de coincidencia, entrada de búsqueda, significado, enlace, sinónimo y antónimo.
  • Si se presiona el botón "Detener búsqueda" durante la ejecución, la repetición se detiene.
Private Sub cmdRunDicSearch_Click()
    Range("A1").Select
    DoEvents
    
    Dim bIsKorDicSearch As Boolean, bIsEngDicSearch As Boolean, sTargetDic As String
    bIsKorDicSearch = chkKorDic.Value: bIsEngDicSearch = chkEngDic.Value
    If (Not bIsKorDicSearch) And (Not bIsEngDicSearch) Then
        MsgBox "검색 대상 사전중 적어도 1개는 선택해야 합니다", vbExclamation + vbOKOnly, "검색 대상 사전 확인"
        Exit Sub
    End If

    Dim bIsMatchTypeExact As Boolean, bIsMatchTypeTermOr As Boolean, bIsMatchTypeAllTerm As Boolean '검색결과 표시 설정
    bIsMatchTypeExact = chkMatchTypeExact.Value: bIsMatchTypeTermOr = chkMatchTypeTermOr.Value: bIsMatchTypeAllTerm = chkMatchTypeAllTerm.Value

    If (bIsMatchTypeExact Or bIsMatchTypeTermOr Or bIsMatchTypeAllTerm) = False Then
        MsgBox "검색결과 표시 설정중 적어도 하나는 선택해야 합니다.", vbExclamation + vbOKOnly, "확인"
        Exit Sub
    End If

    If bIsKorDicSearch And Not bIsEngDicSearch Then sTargetDic = "국어사전"
    If Not bIsKorDicSearch And bIsEngDicSearch Then sTargetDic = "영어사전"
    If bIsKorDicSearch And bIsEngDicSearch Then sTargetDic = "국어사전, 영어사전"
    
    Dim lMaxResultCount As Long
    lMaxResultCount = CInt(txtMaxResultCount.Value)

    If MsgBox("사전 검색을 시작하시겠습니까?" + vbLf + _
              "대상 사전: " + sTargetDic + vbLf + _
              "결과출력 제한개수: " + CStr(lMaxResultCount) _
              , vbQuestion + vbYesNoCancel, "확인") <> vbYes Then Exit Sub

    Dim i As Long, iResultOffset As Long
    bIsWantToStop = False
    DoEvents

    Dim sWord As String, oKorDicSearchResult As TDicSearchResult, oEngDicSearchResult As TDicSearchResult
    Dim oBaseRange As Range
    Set oBaseRange = Range("검색결과Header").Offset(1, 0)
    oBaseRange.Select
    For i = 0 To 100000
        If bIsWantToStop Then
            MsgBox "사용자의 요청으로 검색을 중단합니다.", vbInformation + vbOKOnly, "확인"
            Exit For
        End If
        If chkSkipIfResultExists.Value = True And _
           oBaseRange.Offset(i, 1) <> "" Then GoTo Continue_For '이미 내용이 있으면 Skip
        sWord = oBaseRange.Offset(i)
        If sWord = "" Then Exit For
        oBaseRange.Offset(i).Select

        Application.ScreenUpdating = False
        If bIsKorDicSearch Then '국어사전 검색결과 표시
            oKorDicSearchResult = DoDicSearch(dtsKorean, sWord, bIsMatchTypeExact, bIsMatchTypeTermOr, bIsMatchTypeAllTerm, lMaxResultCount)
            oBaseRange.Offset(i, 1).Select
            With oKorDicSearchResult
                oBaseRange.Offset(i, 1) = .sMatchType
                oBaseRange.Offset(i, 2) = .sSearchEntry
                oBaseRange.Offset(i, 3) = .sMeaning
                If oKorDicSearchResult.sLinkURL <> "" Then
                    With ActiveSheet.Hyperlinks.Add(Anchor:=oBaseRange.Offset(i, 4), Address:=.sLinkURL, TextToDisplay:="네이버국어사전 열기: " & .sLinkWord)
                        .Range.Font.Size = 8
                    End With
                End If
                oBaseRange.Offset(i, 5) = .sSynonymList
                oBaseRange.Offset(i, 6) = .sAntonymList
            
            End With
        End If

        If bIsEngDicSearch Then '영어사전 검색결과 표시
            oEngDicSearchResult = DoDicSearch(dtsEnglish, sWord, bIsMatchTypeExact, bIsMatchTypeTermOr, bIsMatchTypeAllTerm, lMaxResultCount)
            'oBaseRange.Offset(i, 7).Select
            With oEngDicSearchResult
                oBaseRange.Offset(i, 7) = .sMatchType
                oBaseRange.Offset(i, 8) = .sSearchEntry
                oBaseRange.Offset(i, 9) = .sMeaning
                If oKorDicSearchResult.sLinkURL <> "" Then
                    With ActiveSheet.Hyperlinks.Add(Anchor:=oBaseRange.Offset(i, 10), Address:=.sLinkURL, TextToDisplay:="네이버영어사전 열기: " & .sLinkWord)
                        .Range.Font.Size = 8
                    End With
                End If
                oBaseRange.Offset(i, 11) = .sSynonymList
                oBaseRange.Offset(i, 12) = .sAntonymList
            
            End With
        End If
        Application.ScreenUpdating = True

Continue_For:
        DoEvents
    Next i

    MsgBox "사전 검색을 완료하였습니다", vbOKOnly + vbInformation
End Sub

2.7. Búsqueda de diccionario (código fuente DoDicSearch)

Esta función envía una solicitud de búsqueda de una palabra de búsqueda, recibe el resultado, extrae el elemento requerido y lo devuelve.

  • Analizando una cadena JSON en un diccionario: línea 49
  • Extraiga matchType, searchEntry, significado, enlace, sinónimo, entrada de antónimo: líneas 53 a 106
Const DICT_ROOT_URL_KO As String = "https://ko.dict.naver.com/"
Const DICT_BASE_URL_KO As String = "https://ko.dict.naver.com/api3/koko/search?query=%s"
Const DICT_ROOT_URL_EN As String = "https://en.dict.naver.com/"
Const DICT_BASE_URL_EN As String = "https://en.dict.naver.com/api3/enko/search?query=%s"

Public Enum DicToSearch
    dtsKorean = 1
    dtsEnglish = 2
    dtsAll = 10
End Enum

Public Type TDicSearchResult
    sWord As String
    sMatchType As String
    sSearchEntry As String
    sMeaning As String
    sLinkURL As String
    sLinkWord As String
    sSynonymList As String
    sAntonymList As String
End Type

Public Function DoDicSearch(aDicToSearch As DicToSearch, aWord As String, _
    bIsMatchTypeExact As Boolean, bIsMatchTypeTermOr As Boolean, bIsMatchTypeAllTerm As Boolean, _
    aMaxResultCount As Long) As TDicSearchResult

    Dim sDicRootURL As String, sBaseURL As String, sURL As String, sURLData As String, sWord As String, oDicSearchResult As TDicSearchResult

    Dim oParsedDic As Dictionary
    Dim oItem As Dictionary, oMeansCollector As Dictionary, oMeans As Dictionary
    Dim oSimWords As Dictionary, oAntWord As Dictionary
    Dim sPOS As String, sMeaning As String, sLinkURL As String, sLinkWord As String
    Dim s유의어 As String, s유의어목록 As String, s반의어 As String, s반의어목록 As String
    Dim sMatchType As String, sSearchEntry As String, sHandleEntry As String

    Select Case aDicToSearch
        Case dtsKorean
            sDicRootURL = DICT_ROOT_URL_KO
            sBaseURL = DICT_BASE_URL_KO
        Case dtsEnglish
            sDicRootURL = DICT_ROOT_URL_EN
            sBaseURL = DICT_BASE_URL_EN
    End Select

    If aWord = "" Then Exit Function
    sWord = URLEncodeUTF8(aWord)
    sURL = Replace(sBaseURL, "%s", sWord)
    sURLData = GetDataFromURL(sURL, "GET", "", "utf-8") 'URL에서 결과 가져오기
    Set oParsedDic = JsonConverter.ParseJson(sURLData) 'JSON결과를 Dictionary로 변환

    Dim lMatchIdx As Long: lMatchIdx = 0
    Dim lResultCount As Long: lResultCount = 0
    For Each oItem In oParsedDic("searchResultMap")("searchResultListMap")("WORD")("items")
        lResultCount = lResultCount + 1
        If (aMaxResultCount <> 0) And (lResultCount > aMaxResultCount) Then Exit For '결과출력 제한개수 초과시 Loop 종료
        s유의어 = "": s반의어 = ""
        lMatchIdx = lMatchIdx + 1
        'If oItem("matchType") <> "exact:entry" Then Exit For

        sHandleEntry = oItem("handleEntry")
        Select Case oItem("matchType")
            Case "exact:entry"
                sLinkWord = sHandleEntry
                sLinkURL = sDicRootURL + oItem("destinationLink")
                If Not bIsMatchTypeExact Then GoTo Continue_InnerFor
            Case "term:or"
                If Not bIsMatchTypeTermOr Then GoTo Continue_InnerFor
            Case "allterm:proximity:1.000000"
                If Not bIsMatchTypeAllTerm Then GoTo Continue_InnerFor
            Case Else
                
        End Select

        sMatchType = sMatchType + IIf(sMatchType = "", "", vbLf) & CStr(lMatchIdx) & ". " & oItem("matchType")
        sSearchEntry = sSearchEntry + IIf(sSearchEntry = "", "", vbLf) & CStr(lMatchIdx) & ". " & sHandleEntry

        For Each oMeansCollector In oItem("meansCollector")
            'Debug.Print "품사: " & oMeansCollector("partOfSpeech")
            sPOS = ""
            If oMeansCollector.Exists("partOfSpeech") Then
                If Not IsNull(oMeansCollector("partOfSpeech")) Then sPOS = oMeansCollector("partOfSpeech")
            End If
            For Each oMeans In oMeansCollector("means")
                'Debug.Print "뜻: " & oMeans("value")
                If oMeans.Exists("value") Then
                    If Not IsNull(oMeans("value")) Then _
                        sMeaning = sMeaning + IIf(sMeaning = "", "", vbLf) & CStr(lMatchIdx) & ". " & IIf(sPOS = "", "", "[" & sPOS & "] ") & RemoveHTML(oMeans("value"))
                End If
            Next oMeans
        Next oMeansCollector
        For Each oSimWords In oItem("similarWordList")
            If oSimWords.Exists("similarWordName") Then _
                s유의어 = s유의어 + IIf(s유의어 = "", "", ", ") & RemoveHTML(oSimWords("similarWordName"))
        Next oSimWords
        If s유의어 <> "" Then _
            s유의어목록 = s유의어목록 & IIf(s유의어목록 = "", "", vbLf) & CStr(lMatchIdx) & ". " & sHandleEntry & ": " & s유의어

        For Each oAntWord In oItem("antonymWordList")
            If oAntWord.Exists("antonymWordName") Then _
                s반의어 = s반의어 + IIf(s반의어 = "", "", ", ") & RemoveHTML(oAntWord("antonymWordName"))
        Next oAntWord
        If s반의어 <> "" Then _
            s반의어목록 = s반의어목록 & IIf(s반의어목록 = "", "", vbLf) & CStr(lMatchIdx) & ". " & sHandleEntry & ": " & s반의어

Continue_InnerFor:
    Next oItem

    If sMeaning = "" Then
        sMeaning = "#NOT FOUND#": sMatchType = sMeaning: sSearchEntry = sMeaning
    End If

    '결과값 반환
    With oDicSearchResult
        .sWord = aWord
        .sMatchType = sMatchType
        .sSearchEntry = sSearchEntry
        .sMeaning = sMeaning
        .sLinkWord = sLinkWord
        .sLinkURL = Replace(sLinkURL, "#", "%23") 'Excel에서 #기호를 내부적으로 #20 - #20 으로 치환하는 것을 방지
        .sSynonymList = s유의어목록
        .sAntonymList = s반의어목록
    End With
    DoDicSearch = oDicSearchResult
End Function

Arriba, analizamos el método de operación, las precauciones y el código fuente de esta herramienta. Deje comentarios de aquellos que han usado la herramienta, preguntas y características necesarias.


<< Lista de artículos relacionados >>

2 Respuestas

  1. foto de avatar Neculiti Ivan dice:

    Absolutamente de acuerdo contigo. Es una excelente idea. Te apoyo.

    _ _ _ _ _ _ _ _ _ _ _ _ _ _
    Nekultsy Ivan dxvk github

Deja una respuesta

Tu dirección de correo electrónico no será publicada. Los campos obligatorios están marcados con *

es_ESEspañol