smalltalk
/
osmo-st-all
Archived
1
0
Fork 0

Add 'osmo-st-logging/' from commit 'f900c8fc6ef9b7ff54f0d57d092ac6b9d175460b'

git-subtree-dir: osmo-st-logging
git-subtree-mainline: b31b45c939
git-subtree-split: f900c8fc6e
This commit is contained in:
Holger Hans Peter Freyther 2014-06-04 15:45:02 +02:00
commit b9597ffde5
8 changed files with 571 additions and 0 deletions

2
osmo-st-logging/.gitignore vendored Normal file
View File

@ -0,0 +1,2 @@
*.sw?
fileout.st

View File

@ -0,0 +1,316 @@
"
(C) 2010-2011 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/>.
"
Object extend [
logManager [
<category: '*OsmoLogging-Core'>
^ Osmo.LogManager default
]
logDataContext: aData area: anArea [
<category: '*OsmoLogging-Core'>
(self logManager)
context: 'data' value: aData.
]
logDebug: aMessage area: anArea [
<category: '*OsmoLogging-Core'>
(self logManager)
log: (LogEntry withMsg: aMessage level: LogLevel debug area: anArea context: self)
]
logInfo: aMessage area: anArea [
<category: '*OsmoLogging-Core'>
(self logManager)
log: (LogEntry withMsg: aMessage level: LogLevel info area: anArea context: self)
]
logNotice: aMessage area: anArea [
<category: '*OsmoLogging-Core'>
(self logManager)
log: (LogEntry withMsg: aMessage level: LogLevel notice area: anArea context: self)
]
logError: aMessage area: anArea [
<category: '*OsmoLogging-Core'>
(self logManager)
log: (LogEntry withMsg: aMessage level: LogLevel error area: anArea context: self)
]
logException: aMessage area: anArea [
<category: '*OsmoLogging-Core'>
(self logManager)
exception: (LogEntry withMsg: aMessage
level: LogLevel error
area: anArea context: thisContext parentContext)
]
]
Object subclass: LogEntry [
| level ctx area msg |
<category: 'OsmoLogging-Core'>
<comment: 'I represent a log entry and hold the text, level, area'>
LogEntry class >> withMsg: aMsg level: anLevel area: anArea context: aContext [
^ self new
msg: aMsg;
level: anLevel;
area: anArea;
context: aContext;
yourself.
]
msg [
^ msg
]
msg: aMsg [
msg := aMsg.
]
level [
^ level
]
level: anLevel [
level := anLevel
]
area [
^ area
]
area: anArea [
area := anArea.
]
context [
^ ctx
]
context: aContext [
ctx := aContext.
]
]
Object subclass: LogLevel [
<category: 'OsmoLogging-Core'>
<comment: 'I represent the available levels for log messages'>
LogLevel class >> debug [
^ 1
]
LogLevel class >> info [
^ 3
]
LogLevel class >> notice [
^ 5
]
LogLevel class >> error [
^ 7
]
]
Object subclass: LogArea [
| name enabled level |
<category: 'OsmoLogging-Core'>
<comment: 'I represent a LogArea'>
LogArea class >> defaultForArea: aSymbol [
"Find an Area and place the default into our dictionary"
LogArea allSubclassesDo: [ :each |
(each areaName) = aSymbol
ifTrue: [
^ each default.
].
].
^ nil
]
LogArea class >> default [
<category: 'accessing'>
^ self subclassResponsibility
]
LogArea class >> areaName [
<category: 'accessing'>
^ self subclassResponsibility
]
LogArea class >> areaDescription [
<category: 'accessing'>
^ self subclassResponsibility
]
LogArea class >> availableAreas [
<category: 'accessing'>
^ self allSubclasses collect: [ :each |
Array with: each areaName with: each areaDescription
].
]
enabled [
<category: 'accessing'>
^ enabled
]
enabled: anEnabled [
<category: 'accessing'>
enabled := anEnabled.
]
minLevel [
<category: 'accessing'>
^ level
]
minLevel: aLevel [
<category: 'accessing'>
level := aLevel
]
]
Object subclass: LogTarget [
<category: 'OsmoLogging-Target'>
<comment: 'I will filter and then output the log message'>
print: anEntry [
<category: 'log'>
self subclassResponsibility.
]
exception: anEntry [
<category: 'log'>
self subclassResponsibility.
]
]
LogTarget subclass: LogTranscriptTarget [
<category: 'OsmoLogging-Target'>
<comment: 'I log to the Transcript buffer'>
print: anEntry [
<category: 'log'>
Transcript show: anEntry msg; nl.
]
exception: anEntry [
<category: 'log'>
Transcript show: anEntry msg; nl.
anEntry context backtraceOn: Transcript.
]
]
Object subclass: LogFilter [
<category: 'OsmoLogging-Core'>
<comment: 'I filter based on mood, context and Bangkok Law'>
filter: anEntry [
<category: 'filter'>
"I have to decide if anEntry can pass or should be filtered out, I can
access the logManager of anEntry to access the per process context"
^ self subclassResponsibility
]
]
Object subclass: LogManager [
| target filter areas |
<category: 'OsmoLogging-Core'>
<comment: 'I handle the actual log invocation'>
Log := nil.
LogManager class >> default [
<category: 'instance'>
Log ifNil: [
Log := LogManager new.
Log target: LogTranscriptTarget new.
].
^ Log
]
target: aTarget [
<category: 'private'>
target := aTarget.
]
areas [
<category: 'accessing'>
areas ifNil: [
areas := Dictionary new.
].
^ areas
]
findArea: anArea [
<category: 'private'>
"Find anArea, or ask for a default"
^ (self areas) at: anArea ifAbsent: [
| area |
area := LogArea defaultForArea: anArea.
area ifNotNil: [
(self areas) at: anArea put: area.
].
area.
].
]
handle: anEntry ifTrue: aBlock [
<category: 'private'>
| area |
area := self findArea: anEntry area.
(area enabled and: [anEntry level >= area minLevel]) ifTrue: aBlock
]
log: anEntry [
<category: 'log'>
self handle: anEntry ifTrue: [
target print: anEntry
]
]
exception: anEntry [
<category: 'log'>
self handle: anEntry ifTrue: [
target exception: anEntry.
]
]
context: aString value: aValue [
| key |
key := Array with: 'LogArea' with: aString.
(ProcessVariable key: key) value: aValue.
]
contextValue: aString [
| key |
key := Array with: 'LogArea' with: aString.
^ (ProcessVariable key: key) value.
]
]

View File

@ -0,0 +1,114 @@
"
(C) 2011 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/>.
"
LogTarget subclass: LogTargetSyslog [
| prefix |
<comment: 'I can log everything to the syslog.'>
<category: 'OsmoLogging-Syslog'>
LogMap := nil.
LogTargetSyslog class >> LOG_USER [
<category: 'c-facility'>
^ 8
]
LogTargetSyslog class >> logLevelMap [
^ LogMap ifNil: [ LogMap := Dictionary new
at: LogLevel debug put: 7;
at: LogLevel info put: 6;
at: LogLevel notice put: 5;
at: LogLevel error put: 3;
yourself
]
]
LogTargetSyslog class >> openlog: aIdent option: aOption facility: aFacility [
"Free any previous string"
SYSLOG_NAME ifNotNil: [
SYSLOG_NAME free.
Smalltalk at: #SYSLOG_NAME put: nil.
].
Smalltalk at: #SYSLOG_NAME put: aIdent asCData.
self c_closelog.
self c_openlog: SYSLOG_NAME opt: aOption facility: aFacility.
^ self new
]
LogTargetSyslog class >> c_openlog: ident opt: aOpt facility: aFac [
<category: 'c-interface'>
<cCall: 'openlog' returning: #void args: #(#cObject #int #int)>
]
LogTargetSyslog class >> c_syslog: prio fmt: aFormat args: args[
<category: 'c-interface'>
<cCall: 'syslog' returning: #void args: #(#int #string #variadic)>
]
LogTargetSyslog class >> c_closelog [
<category: 'c-interface'>
<cCall: 'closelog' returning: #void args: #()>
]
LogTargetSyslog class >> initialize [
<category: 'c-interface'>
DLD addLibrary: 'libc'.
"Workaround Debian multiarch issues in finding libc"
DLD addLibrary: 'libm'.
ObjectMemory addDependent: self.
]
LogTargetSyslog class >> update: aSymbol [
"We need to forget the C String we have allocated as we are running
in a new VM right now. Maybe we will be re-opened by someone."
aSymbol = #returnFromSnapshot ifTrue: [
Smalltalk at: #SYSLOG_NAME put: nil.
].
]
print: aMessage [
<category: 'output'>
| level |
level := self class logLevelMap at: aMessage level.
self class c_syslog: level fmt: '%s%s' args: {self prefix. aMessage msg}.
]
exception: aMessage [
| level |
level := self class logLevelMap at: aMessage level.
self class c_syslog: level fmt: '%s%s'
args: {self prefix. 'EXCEPTION occured'}.
self print: aMessage.
]
prefix: aMsg [
prefix := aMsg.
]
prefix [
^ prefix ifNil: ['']
]
]
Eval [
LogTargetSyslog initialize.
]

View File

@ -0,0 +1,70 @@
"
(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/>.
"
PackageLoader fileInPackage: #OsmoLogging.
Osmo.LogArea subclass: LogAreaSCCP [
LogAreaSCCP class >> areaName [
^ #sccp
]
LogAreaSCCP class >> areaDescription [
^ 'SCCP related'
]
LogAreaSCCP class >> default [
^ self new
enabled: true;
minLevel: LogLevel debug;
yourself
]
]
Eval [
| syslog |
'123' logDebug: 'TEST' area: #sccp.
'123' logException: 'TEST' area: #sccp.
"SYSLOG"
syslog := (Osmo.LogTargetSyslog
openlog: 'ow' option: 0 facility: Osmo.LogTargetSyslog LOG_USER).
syslog prefix: 'abc:'.
Object logManager target: syslog.
'123' logError: 'Error message' area: #sccp.
[
'123' error: 'ABC DEF'.
] on: Error do: [:e |
e logException: 'Exception... ' area: #sccp.
].
Object logManager target:
(Osmo.LogTargetSyslog
openlog: 'ow2' option: 0 facility: Osmo.LogTargetSyslog LOG_USER).
'123' logError: 'Error message' area: #sccp.
[
'123' error: 'ABC DEF'.
] on: Error do: [:e |
e logException: 'Exception... ' area: #sccp.
].
]

17
osmo-st-logging/Makefile Normal file
View File

@ -0,0 +1,17 @@
GST_PACKAGE = gst-package
GST_CONVERT = gst-convert
CONVERT_RULES = -r'Osmo.LogManager->LogManager' \
-r'(Transcript nl)->(Transcript cr)' \
-r'(thisContext parentContext)->(thisContext sender)' \
-r'(``@object backtraceOn: ``@args1)->(``@object printOn: ``@args1)' \
-r'ProcessVariable->GSTProcessVariable'
all:
$(GST_PACKAGE) --test package.xml
convert:
$(GST_CONVERT) $(CONVERT_RULES) -F squeak -f gst \
-o fileout.st compat_for_pharo.st LogManager.st

7
osmo-st-logging/README Normal file
View File

@ -0,0 +1,7 @@
A Smalltalk logging framework inspired by libosmocore's logging facilities
Core Features:
- Categories
- Filters
- Multiple backends
- Integration with libosmocore (somehow)

View File

@ -0,0 +1,35 @@
Object subclass: GSTProcessVariableHolder [
| val |
<category: 'OsmoLogging-Pharo'>
value: aValue [
<category: 'set'>
val := val.
]
value [
<category: 'get'>
^ val
]
]
ProcessLocalVariable subclass: GSTProcessVariable [
| dict |
<category: 'OsmoLogging-Pharo'>
GSTProcessVariable class >> key: aKey [
<category: 'creation'>
^ self soleInstance key: aKey.
]
dict [
<category: 'creation'>
^ dict ifNil: [dict := Dictionary new].
]
key: aKey [
<category: 'key'>
^ self dict at: aKey ifAbsent:
[self dict at: aKey put: GSTProcessVariableHolder new].
]
]

View File

@ -0,0 +1,10 @@
<package>
<name>OsmoLogging</name>
<namespace>Osmo</namespace>
<filein>LogManager.st</filein>
<filein>LogSyslog.st</filein>
<file>LogManager.st</file>
<file>LogTest.st</file>
</package>