Resultados 1 al 7 de 7

Tema: Convertir LibreOffice Basic a COBOL¿?

  1. #1
      Acabo de llegar...
    X

    Registrado
    enero de 2016
    Ubicación
    Valencia
    Mensajes
    24
    Última visita
    10.09.2022

    Agradecimientos
     
    Recibidos
    3
    Enviados
    13

    Citaciones y menciones
     
    Mentioned
    4 Post(s)
    Tagged
    0 Thread(s)
    Quoted
    0 Post(s)
    Poder de Reputación
    0

    Predeterminado Convertir LibreOffice Basic a COBOL¿?

    Buenos días. Alguien sabría "traducir" esta instrucción (marcada con --->) hecha con Basic de LibreOffice a instrucciones COBOL?:

    VB Código:
    1. Sub AbriendoDocumentos4()
    2.  Dim sRuta As String
    3. --->  Dim mOpciones(0) As New "com.sun.star.beans.PropertyValue"
    4.  Dim oDoc As Object
    5.  
    6.      mOpciones(0).Name = "AsTemplate"
    7.      mOpciones(0).Value = True
    8.  
    9.      sRuta = ConvertToUrl( "/home/Mi archivo de Writer.odt" )
    10.      oDoc = StarDesktop.loadComponentFromURL( sRuta, "_blank", 0, mOpciones() )
    11.  
    12.  End Sub

    Agradecería cualquier ayuda. Estoy intentando pasar mis aplicaciones hechas para acceder a Word a poder hacerlo con LibreOffice Writer

    0 Not allowed!

  2. #2
      Administrador
    Avatar de Kuk

    Registrado
    enero de 2015
    Ubicación
    Madrid
    Edad
    39
    Mensajes
    2,290
    Última visita
    Hoy a las 15:46

    Agradecimientos
     
    Recibidos
    1,038
    Enviados
    888

    Citaciones y menciones
     
    Mentioned
    104 Post(s)
    Tagged
    0 Thread(s)
    Quoted
    31 Post(s)
    Poder de Reputación
    10

    Predeterminado

    @Xavier, intenta a ver:

    COBOL Código:
    1.  ENVIRONMENT     DIVISION.
    2.  DATA            DIVISION.
    3.  WORKING-STORAGE SECTION.
    4.  01  TXT             PIC X(50).
    5.  01  mOpciones       OBJECT REFERENCE COM.
    6.  PROCEDURE       DIVISION.
    7.      
    8.      MOVE "com.sun.star.beans.PropertyValue" TO TXT    
    9.      INVOKE COM "CREATE-OBJECT" USING TXT RETURNING mOpciones
    10.  
    11.      INVOKE mOpciones "set-Name" USING "AsTemplate"
    12.      INVOKE mOpciones "set-Value" USING -1 *>True
    13.  


    Y échale un ojo a este post: [Aporte] Uso del ChartControl de Codejock - COBOL Foro

    0 Not allowed!
    ¿Te han ayudado? NO TE OLVIDES de darle al botón
    ¿Quieres dirigirte a alguien en tu post? Notifícale con una mención, tienes 2 opciones:
    1. Haciendo clic en el icono al lado de su nick
    2. Haciendo clic en el botón en el editor y escribiendo su nick.

  3. #3
      Acabo de llegar...
    X

    Registrado
    enero de 2016
    Ubicación
    Valencia
    Mensajes
    24
    Última visita
    10.09.2022

    Agradecimientos
     
    Recibidos
    3
    Enviados
    13

    Citaciones y menciones
     
    Mentioned
    4 Post(s)
    Tagged
    0 Thread(s)
    Quoted
    0 Post(s)
    Poder de Reputación
    0

    Predeterminado

    Gracias Kuk, ya había intentado definir así la variable
    COBOL Código:
    1.  01 ServProperty        PIC X(32) VALUE "com.sun.star.beans.PropertyValue".
    2.  01 objArgs         OBJECT REFERENCE COM.

    Pero, al trazar el programa y ejecutar la instrucción:
    COBOL Código:
    1.   "INVOKE COM "Create-Object" USING ServProperty RETURNING objArgs

    Me da el siguiente error:
    CODE Código:
    1. "Exception ocurrence(Exception object)

    Voy a echar una ojeada al "Aporte" que me has pasado


    Mensaje de MODERADOR

    Utiliza las etiquetas de resalto de sintaxis (los botones, Cobol, SQL etc en el editor)

    0 Not allowed!

  4. #4
      Administrador
    Avatar de Kuk

    Registrado
    enero de 2015
    Ubicación
    Madrid
    Edad
    39
    Mensajes
    2,290
    Última visita
    Hoy a las 15:46

    Agradecimientos
     
    Recibidos
    1,038
    Enviados
    888

    Citaciones y menciones
     
    Mentioned
    104 Post(s)
    Tagged
    0 Thread(s)
    Quoted
    31 Post(s)
    Poder de Reputación
    10

    Predeterminado

    @Xavier, habría que sacar la descripción del error más detallada.

    Aquí tienes un ejemplo de cómo declarar las excepciones en DECLARATIVES: [Aporte] Exportar CmListview en Excel - COBOL Foro

    También échale un ojo a esto: [Sintaxis] Como descifrar valores de COM-EXCEPTION - COBOL Foro

    0 Not allowed!
    ¿Te han ayudado? NO TE OLVIDES de darle al botón
    ¿Quieres dirigirte a alguien en tu post? Notifícale con una mención, tienes 2 opciones:
    1. Haciendo clic en el icono al lado de su nick
    2. Haciendo clic en el botón en el editor y escribiendo su nick.

  5. #5
      Senior
    Avatar de fastpho

    Registrado
    diciembre de 2016
    Ubicación
    Mendoza
    Edad
    53
    Mensajes
    326
    Última visita
    18.04.2024

    Agradecimientos
     
    Recibidos
    226
    Enviados
    209

    Citaciones y menciones
     
    Mentioned
    49 Post(s)
    Tagged
    0 Thread(s)
    Quoted
    15 Post(s)
    Poder de Reputación
    21
    Innovación / Point Value: 0 Concurso: Primer puesto / Point Value: 0

    Predeterminado

    @Xavier, Buscando en la web encontre dos ejemplos de OpenOffice en Net Express , creo que funcionan habria que convertirlos a powercobol
    Ejemplo 1
    COBOL Código:
    1. $set ooctrl(+P)
    2. IDENTIFICATION DIVISION.
    3. ENVIRONMENT DIVISION.
    4.  
    5. class-control.
    6. OServManager is class "$OLE$com.sun.star.ServiceManager"
    7. oleSafeArray is class "olesafea" OLE SafeArray class
    8. .
    9.  
    10. DATA DIVISION.
    11. WORKING-STORAGE SECTION.
    12.  
    13. copy mfole.cpy.
    14.  
    15.  
    16. *---SafeArray dimension structure SafeArrayBound
    17. * celements is the total number of elements
    18. * lBound is the lower boundary (usually 0)
    19. 01 tagSafeArrayBound is typedef.
    20. 05 celements usage ULONG.
    21. 05 llbound usage LONG.
    22. 01 SafeArrayBound is typedef usage tagSafeArrayBound.
    23. 01 saBound SafeArrayBound.
    24.  
    25.  
    26. 01 ServManager object reference.
    27. 01 StarDesktop object reference.
    28. 01 aDoc object reference.
    29. 01 atext object reference.
    30.  
    31. 01 Group1SafeArray object reference.
    32.  
    33. 01 theVarType VARTYPE.
    34.  
    35. 01 cDims UINT.
    36.  
    37. *-----------------------------------------------------------------
    38. PROCEDURE DIVISION.
    39.  
    40. Start-Up. # Start-Up
    41. *--- create the document
    42. perform CreateDocument-Stup.
    43.  
    44. *--- fill the document with some text
    45. perform FillDocument-Stup.
    46.  
    47. exit program.
    48. stop run.
    49.  
    50. *-----------------------------------------------------------------
    51. CreateDocument-Stup. # CreateDocument-Stup
    52. *---
    53. invoke OServManager "new" returning ServManager
    54.  
    55. *---
    56. invoke ServManager "createInstance"
    57. using "com.sun.star.frame.Desktop"
    58. returning StarDesktop.
    59.  
    60. *--- olesafearray
    61. move VT-VARIANT to thevarType.
    62. move 1 to cDims.
    63. move 0 to cElements OF saBound.
    64. move 0 to llBound OF saBound.
    65. invoke olesafearray "new" using by value thevarType
    66. by value cDims
    67. by reference saBound
    68. returning Group1SafeArray.
    69.  
    70. *--- loadComponentFromURL
    71. invoke StarDesktop "loadComponentFromURL"
    72. using "private:factory/swriter" change 'swriter' with 'scalc' to call openOffice Calc
    73. "_blank"
    74. "0"
    75. Group1SafeArray
    76. returning aDoc.
    77.  
    78. *-----------------------------------------------------------------
    79. FillDocument-Stup. # FillDocument-Stup
    80. invoke aDoc "GetText" returning aText. remove this line if you call 'Calc'
    81. invoke aText "SetString" using "Hello World". remove this line if you call 'Calc'
    82.  
    83. *-----------------------------------------------------------------
    Ejemplo 2 :
    COBOL Código:
    1.  $set sourceformat(variable)                                                                    
    2.       $set ooctrl( P)                                                                                
    3.        IDENTIFICATION DIVISION.                                                                      
    4.        ENVIRONMENT DIVISION.                                                                        
    5.                                                                                                      
    6.        class-control.                                                                                
    7.            OServManager is class "$OLE$com.sun.star.ServiceManager"                                  
    8.            oleSafeArray is class "olesafea"  *> OLE SafeArray class                                  
    9.            olesup is class "olesup"                                                                  
    10.            OLEVariant is class "olevar"                                                              
    11.             olebase is class "olebase"                                                              
    12.            .                                                                                        
    13.                                                                                                      
    14.        DATA DIVISION.                                                                                
    15.         WORKING-STORAGE SECTION.                                                                    
    16.                                                                                                      
    17.        copy mfole.cpy.                                                                              
    18.                                                                                                      
    19.        copy olesafea.cpy.            *> SafeArray records                                            
    20.                                                                                                      
    21.        01 theSafeArrayObj  object reference.                                                        
    22.                                                                                                      
    23.        01 saBound          SAFEARRAYBOUND.                                                          
    24.                                                                                                      
    25.        01 ServManager          object reference.                                                    
    26.        01 StarDesktop          object reference.                                                    
    27.        01 aDoc object reference.                                                                    
    28.        01 aSheets object reference.                                                                  
    29.        01 aSheet object reference.                                                                  
    30.        01 aCell object reference.                                                                    
    31.        01 aTempObj object reference.                                                                
    32.        01 oPropertyValue  object reference.                                                          
    33.        01 hResult            pic 9(9) comp-5.                                                        
    34.        01 iIndex               pic 9(9) comp-5 value 0.                                              
    35.            PROCEDURE DIVISION.                                                                      
    36.                                                                                                      
    37.            invoke OServManager "new" returning ServManager                                          
    38.                                                                                                      
    39.            invoke ServManager "createInstance" using "com.sun.star.frame.Desktop" returning StarDeskto
    40.                                                                                                      
    41.            move 0 to llBound   of saBound                                                            
    42.            move 1 to cElements of saBound                                                            
    43.            invoke olesafearray "new" using                                                          
    44.                by value VT-VARIANT                                                                  
    45.                by value 1                  *> Single dimension                                      
    46.                by reference saBound        *> Dimension boundaries                                  
    47.                returning theSafeArrayObj                                                            
    48.                                                                                                      
    49.            invoke StarDesktop "loadComponentFromURL" using                                          
    50.                by reference "private:factory/scalc"                                                  
    51.                by reference "_blank"                                                                
    52.                by value 0                                                                            
    53.                by reference theSafeArrayObj                                                          
    54.                returning aDoc                                                                        
    55.                                                                                                      
    56.            invoke aDoc "getSheets" returning aSheets                                                
    57.                                                                                                      
    58.            invoke olesup "setDispatchType" using by value 0   *> value 0 = next message forced to invoke
    59.            invoke aSheets "getByName" using by reference "Sheet1" returning aSheet                    
    60.                                                                                                      
    61.            invoke olesup "setDispatchType" using by value 0   *> value 0 = next message forced to invoke
    62.            invoke aSheet "getCellByPosition" using by value 0, by value 0 returning aCell            
    63.            invoke aCell "SetString" using "Hello World"                                              
    64.                                                                                                      
    65.            invoke ServManager "Bridge_GetStruct" using "com.sun.star.beans.PropertyValue" returning oP
    66.                                                                                                      
    67.            invoke olesup "setDispatchType" using by value 1   *> value 1 = next message forced to invoke
    68.            invoke oPropertyValue "Name" using Z"FilterName"                                          
    69.                                                                                                      
    70.            invoke olesup "setDispatchType" using by value 1   *> value 1 = next message forced to invoke
    71.            invoke oPropertyValue "Value" using Z"MS Excel 97"                                        
    72.            invoke theSafeArrayObj "putOLEObject"                                                    
    73.               using Iindex                                                                          
    74.                     by value oPropertyValue                                                          
    75.               returning hResult                                                                      
    76.            end-invoke.                                                                                
    77.            invoke aDoc "storeAsURL" using                                                            
    78.                by reference Z"file:///C:/cobol/calctstx.xls"                
    79.                by reference theSafeArrayObj                                                          
    80.                                                                                                      
    81.      *>   Finalize all objects                                                                      
    82.            invoke aCell "finalize" returning aCell                                                  
    83.            invoke aSheet "finalize" returning aSheet                                                
    84.            invoke aSheets "finalize" returning aSheets                                              
    85.                                                                                                      
    86.            invoke aDoc "Close" using by value -1                                                      
    87.            invoke aDoc "Finalize" returning aDoc                                                    
    88.            invoke StarDesktop "Finalize" returning StarDesktop                                      
    89.            invoke ServManager "Finalize" returning ServManager                                      
    90.                                                                                                      
    91.            goback.                                                                                  
    Saludos

    0 Not allowed!

  6. #6
      Acabo de llegar...
    X

    Registrado
    enero de 2016
    Ubicación
    Valencia
    Mensajes
    24
    Última visita
    10.09.2022

    Agradecimientos
     
    Recibidos
    3
    Enviados
    13

    Citaciones y menciones
     
    Mentioned
    4 Post(s)
    Tagged
    0 Thread(s)
    Quoted
    0 Post(s)
    Poder de Reputación
    0

    Predeterminado

    Hola @Kuk, ya hago uso de los controles para obtener una descripción más detallada del error, pero no me saca nada, solo un código de error, que lo he buscado por internet y no he conseguido ningún resultado
    Esto es lo que me sale del error:

    CODE Código:
    1. Error Type: 1
    2. wCode: +0000
    3. SCode: -147352571
    4. SCode-Text:
    5. Error Descr:

    ---------- Post añadido : 11:22 ---------- Post anterior : 11:02 ----------

    Hola @fastpho, me parece muy interesante tu aporte. Voy a trabajar en ello y ya os digo algo

    0 Not allowed!

  7. #7
      Administrador
    Avatar de Kuk

    Registrado
    enero de 2015
    Ubicación
    Madrid
    Edad
    39
    Mensajes
    2,290
    Última visita
    Hoy a las 15:46

    Agradecimientos
     
    Recibidos
    1,038
    Enviados
    888

    Citaciones y menciones
     
    Mentioned
    104 Post(s)
    Tagged
    0 Thread(s)
    Quoted
    31 Post(s)
    Poder de Reputación
    10

    Predeterminado

    @Xavier, creo recordar que había que hacer llamadas adicionales para sacar la descripción del error.

    0 Not allowed!
    ¿Te han ayudado? NO TE OLVIDES de darle al botón
    ¿Quieres dirigirte a alguien en tu post? Notifícale con una mención, tienes 2 opciones:
    1. Haciendo clic en el icono al lado de su nick
    2. Haciendo clic en el botón en el editor y escribiendo su nick.

Información de Tema

Usuarios Viendo este Tema

Actualmente hay 1 usuarios viendo este tema. (0 miembros y 1 visitantes)

Temas Similares

  1. [Información] Alguien utiliza Power-LibreOffice?
    Por Xavier en el foro PowerCOBOL (ActiveX, v4 - v11)
    Respuestas: 0
    Último Mensaje: 08.07.2021, 20:11
  2. [Sintaxis] Convertir DECIMAL a NUMERO para COBOL
    Por Dasije en el foro WinDev
    Respuestas: 0
    Último Mensaje: 11.08.2019, 23:44
  3. [Información] Eejempo: convertir string binario en valor
    Por Kuk en el foro Micro Focus COBOL
    Respuestas: 0
    Último Mensaje: 09.08.2019, 16:24
  4. [Herramienta] Convertir Label a JPG
    Por Anthony en el foro AcuCobol
    Respuestas: 2
    Último Mensaje: 23.07.2016, 00:54
  5. [Componente] OCR para convertir la IMG a texto
    Por Roger en el foro PowerCOBOL (ActiveX, v4 - v11)
    Respuestas: 8
    Último Mensaje: 06.03.2015, 12:24

Marcadores

Marcadores

Permisos de Publicación

  • No puedes crear nuevos temas
  • No puedes responder temas
  • No puedes subir archivos adjuntos
  • No puedes editar tus mensajes
  •