1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-binding/OsmoVTY.st

254 lines
6.6 KiB
Smalltalk

"
(C) 2010 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as
published by the Free Software Foundation, either version 3 of the
License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
CStruct subclass: Vty_app_info [
<category: 'OsmoBinding'>
<comment: 'I represent the vty_app_info... some structs are wrong'>
<declaration: #(
#(#name #string)
#(#version #string)
#(#copyright #string)
#(#tall_ctx #(#ptr #int))
#(#go_parent_cb #(#ptr #long))
#(#is_config_node #(#ptr #long))) >
]
CStruct subclass: Vty_vector [
<category: 'OsmoBinding'>
<comment: 'I am the struct _vector class'>
"the index is wrong but we do not need to access it"
<declaration: #(
#(#active #uInt)
#(#alloced #uInt)
#(#index #(#ptr #int))) >
]
CStruct subclass: Vty_cmd_element [
<category: 'OsmoBinding'>
<comment: 'I represent the lowlevel command'>
<declaration: #(
#(#name #string)
#(#func #(#ptr #int))
#(#doc #string)
#(#daemon #int)
#(#strvec #(#ptr #{Vty_vector}))
#(#cmdsize #uInt)
#(#config #string)
#(#subconfig #(#ptr #{Vty_vector}))
#(#attr #uChar))>
]
CStruct subclass: Vty_cmd_node [
<category: 'OsmoBinding'>
<comment: 'I provide access to a cmd_node'>
<declaration: #(
#(#node #int)
#(#prompt #string)
#(#vtysh #int)
#(#func #(#ptr #int))
#(#cmd_vector #(#ptr #{Vty_vector}))) >
]
Object subclass: NodeType [
<category: 'libosmovty'>
NodeType class >> AUTH_NODE [
^ 0
]
NodeType class >> VIEW_NODE [
^ 1
]
NodeType class >> AUTH_ENABLE_NODE [
^ 2
]
NodeType class >> ENABLE_NODE [
^ 3
]
NodeType class >> CONFIG_NODE [
^ 4
]
NodeType class >> SERVICE_NODE [
^ 5
]
NodeType class >> DEBUG_NODE [
^ 6
]
NodeType class >> VTY_NODE [
^ 7
]
]
Object subclass: OSMOVTY [
<category: 'OsmoBinding'>
<comment: 'I provide access to the VTY code'>
OSMOVTY class >> initialize [
DLD addLibrary: 'libosmovty.so.0'
]
OSMOVTY class >> vty_init: app_info [
<cCall: 'vty_init' returning: #void args: #(#cObject) >
]
OSMOVTY class >> vty_read_config_file: file_name priv: priv [
<cCall: 'vty_read_config_file' returning: #int args: #(#string (#ptr #long)) >
]
OSMOVTY class >> telnet_init: tall_context priv: priv port: aPort [
<cCall: 'telnet_init' returning: #int args: #(#cObject #cObject #int) >
]
OSMOVTY class >> install_node: aNode func: aFunc [
<cCall: 'install_node' returning: #void args: #(#cObject #cObject) >
]
OSMOVTY class >> install_default: aNode [
<cCall: 'install_default' returning: #void args: #(#int) >
]
OSMOVTY class >> install_element: aNode cmd: aCmd [
<cCall: 'install_element' returning: #void args: #(#int #{Vty_cmd_element}) >
]
OSMOVTY class >> install_element_ve: aCmd [
<cCall: 'install_element_ve' returning: #void args: #(#{Vty_cmd_element}) >
]
OSMOVTY class >> vty_out: aVty msg: aMsg [
<cCall: 'vty_out' returning: #int args: #(#cObject #string) >
]
OSMOVTY class >> vty_out_newline: aVty [
<cCall: 'vty_out_newline' returning: #int args: #(#cObject) >
]
OSMOVTY class >> initWith: aName version: aVersion license: aLicense port: aPort [
| app_info |
app_info := Vty_app_info new.
app_info name value: aName.
app_info version value: aVersion.
app_info copyright value: aLicense.
app_info tall_ctx value: 0.
app_info go_parent_cb value: 0.
app_info is_config_node value: 0.
OSMOVTY vty_init: app_info.
OSMOVTY telnet_init: nil priv: nil port: 4444.
]
OSMOVTY class >> commands [
^ Smalltalk at: #VTY_Commands ifAbsent: [
| array |
array := OrderedCollection new.
Smalltalk at: #VTY_Commands put: array.
array.
]
]
]
Object subclass: VTYCommand [
<category: 'OsmoBinding'>
<comment: 'I represent a vty command with a callback'>
| command callback handler |
VTYCommand class >> initWith: aCommand help: aHelp handler: aBlock[
<category: 'creation'>
"Create a new command. The memory is allocated permamently"
| command |
command := Vty_cmd_element gcNew.
command name value: aCommand.
command doc value: aHelp.
^ (self new)
command: command;
handler: aBlock;
yourself.
]
handleCommand: aCmd vty: aVty argc: aArgc argv: aArgv [
| str strings |
<category: 'private'>
str := aArgv castTo: CStringType.
strings := OrderedCollection new.
0 to: (aArgc - 1) do: [ :each |
strings add: (str at: each).
].
^ handler value: aVty value: strings.
]
handler: aBlock [
<category: 'private'>
handler := aBlock.
]
command: aCommand [
<category: 'private'>
"We need to know when we are removed as we will segfault soon"
self addToBeFinalized.
command := aCommand.
callback := CCallbackDescriptor
for: [ :cmd :vty :argc :argv |
self handleCommand: cmd vty: vty argc: argc argv: argv.
]
returning: #int
withArgs: #(#cObject #cObject #int #cObject).
command func value: callback.
]
command [
<category: 'command'>
^ command
]
finalize [
self error: 'The command can not be removed. A crash will happen soon.'
]
install_ve [
<category: 'install'>
OSMOVTY commands add: self.
OSMOVTY install_element_ve: command.
]
install: aNode [
<category: 'install'>
OSMOVTY commands add: self.
OSMOVTY install_element: aNode cmd: command.
]
]
Eval [
OSMOVTY initialize.
]