MiniLogger.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 26 Aug 2014 10:43:40 +0200
changeset 16826 a7fd70258cef
parent 16784 05fdf667949e
child 16845 d3c79db6b338
permissions -rw-r--r--
Major refactoring of MiniLogger (part 1) - use predefined set of severities - added more convenience logging methods.

"
 COPYRIGHT (c) 2012-2014 by Jan Vrany & eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libbasic' }"

Object subclass:#MiniLogger
	instanceVariableNames:''
	classVariableNames:'ALL ENTER LEAVE TRACE3 TRACE2 TRACE1 TRACE0 TRACE DEBUG INFO WARN
		ERROR FATAL NONE Severities Threshold Instance'
	poolDictionaries:''
	category:'System-Debugging-Support'
!

Object subclass:#Severity
	instanceVariableNames:'name value'
	classVariableNames:''
	poolDictionaries:''
	privateIn:MiniLogger
!

!MiniLogger class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2012-2014 by Jan Vrany & eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
! !

!MiniLogger class methodsFor:'initialization'!

initialize
    "Invoked at system start or when the class is dynamically loaded."
    "/ please change as required (and remove this comment)
    
    ALL := Severity new initializeWithName:#all value:0.
    ENTER := Severity new initializeWithName:#enter value:10.
    LEAVE := Severity new initializeWithName:#leave value:10.
    TRACE3 := Severity new initializeWithName:#trace3 value:20.
    TRACE2 := Severity new initializeWithName:#trace2 value:30.
    TRACE1 := Severity new initializeWithName:#trace1 value:40.
    TRACE0 := Severity new initializeWithName:#trace0 value:50.
    TRACE := Severity new initializeWithName:#trace value:50.
    DEBUG := Severity new initializeWithName:#debug value:60.
    INFO := Severity new initializeWithName:#info value:70.
    WARN := Severity new initializeWithName:#warn value:88.
    ERROR := Severity new initializeWithName:#error value:99.
    FATAL := Severity new initializeWithName:#fatal value:100.
    NONE := Severity new initializeWithName:#none value:65535.

    Severities := Array new:12.
    Severities at:1 put:ENTER.
    Severities at:2 put:LEAVE.
    Severities at:3 put:TRACE3.
    Severities at:4 put:TRACE2.
    Severities at:5 put:TRACE1.
    Severities at:6 put:TRACE0.
    Severities at:7 put:TRACE.
    Severities at:8 put:DEBUG.
    Severities at:9 put:INFO.
    Severities at:10 put:WARN.
    Severities at:11 put:ERROR.
    Severities at:12 put:FATAL.

    Threshold := INFO.

    (Smalltalk at:#Logger) isNil ifTrue:[
        Smalltalk at:#Logger put:self
    ].

    "Modified: / 13-08-2014 / 14:36:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MiniLogger class methodsFor:'accessing-severities'!

severityDEBUG
    ^ DEBUG

    "Created: / 13-08-2014 / 14:15:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

severityENTER
    ^ ENTER

    "Created: / 13-08-2014 / 14:14:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

severityERROR
    ^ ERROR

    "Created: / 13-08-2014 / 14:15:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

severityFATAL
    ^ FATAL

    "Created: / 13-08-2014 / 14:15:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

severityINFO
    ^ INFO

    "Created: / 13-08-2014 / 14:15:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

severityLEAVE
    ^ LEAVE

    "Created: / 13-08-2014 / 14:14:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

severityTRACE
    ^ TRACE

    "Created: / 13-08-2014 / 14:15:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

severityTRACE0
    ^ TRACE0

    "Created: / 13-08-2014 / 14:14:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

severityTRACE1
    ^ TRACE1

    "Created: / 13-08-2014 / 14:14:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

severityTRACE2
    ^ TRACE2

    "Created: / 13-08-2014 / 14:14:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

severityTRACE3
    ^ TRACE3

    "Created: / 13-08-2014 / 14:14:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

severityWARN
    ^ WARN

    "Created: / 13-08-2014 / 14:15:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MiniLogger class methodsFor:'accessing-severities-special'!

severityALL
    ^ ALL

    "Created: / 13-08-2014 / 14:14:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

severityNONE
    ^ NONE

    "Created: / 13-08-2014 / 14:15:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MiniLogger class methodsFor:'configuration'!

loggingThreshold
    "Return the logging threshold. No messages with severity lower than 
     threshold will be logged."
    
    ^ Threshold

    "Created: / 13-08-2014 / 14:36:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

loggingThreshold:severity 
    "Sets logging threshold. No severity lower than given one will be logged.
     Use `Logger severityNONE` to suppress logging completely or
     `Logger severityALL` to log all messages"
    
    ((Severities includes:severity) 
        or:[ severity == ALL or:[ severity == NONE ] ]) 
            ifFalse:[
                self error:'Invalid severity. Use of Logger severityXXX'.
                ^ self.
            ].
    Threshold := severity

    "Created: / 13-08-2014 / 14:34:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 26-08-2014 / 08:23:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MiniLogger class methodsFor:'logging'!

log: message
    self log: message severity: DEBUG

    "Created: / 15-09-2011 / 10:27:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-08-2014 / 14:12:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

log: message facility: facility
    self log: message severity: DEBUG facility: facility

    "Created: / 14-09-2011 / 21:22:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-08-2014 / 14:12:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

log: message severity: severity
    | originator |

    originator := thisContext sender receiver.   
    self log: message severity: severity originator: originator

    "Created: / 15-09-2011 / 10:25:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 26-08-2014 / 08:23:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

log: message severity: severity attachment: attachment
    | originator |

    originator := thisContext sender receiver.
    self log: message severity: severity facility: (self facilityOf: originator) originator: originator attachment: attachment

    "Created: / 15-09-2011 / 11:47:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 15-03-2013 / 11:20:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 26-08-2014 / 08:23:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

log: message severity: severity facility: facility
    self log: message severity: severity facility: facility originator: thisContext sender receiver

    "Created: / 14-09-2011 / 21:20:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

log: message severity: severity facility: facility originator: originator
    self log: message severity: severity facility: facility originator: originator attachment: nil

    "Created: / 14-09-2011 / 21:20:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

log: message severity: severity facility: facility originator: originator attachment: attachment
    "Pricipal logging method. This mimics VM __stxLog__()"

    | severityXlated |

    severityXlated := severity.

    "/ Be backward compatible, allow for symbolic severities
    "/ but when encountered, issue a warning...
    severity isSymbol ifTrue:[ 
        | nseverities i |

        i := 1.
        nseverities := Severities size.
        [ i <= nseverities ] whileTrue:[
            | s | 

            (s := Severities at: i) name = severity ifTrue:[ 
                | caller |    
                severityXlated := s.
                i := nseverities + 1. "/ exit the loop

                "/ This will be enabled later, so far it generates
                "/ way to much warnings. at least stx:libjava & exept:jdi has to be rewritten
                
                "/ self log: 'using symbols as severity is deprecated, use Logger severityXXX to get severity object' severity: WARN facility: 'STX' originator: self.
                "/ caller := thisContext sender.
                "/ [ caller notNil and: [ caller receiver ~~ originator ] ] whileTrue:[ caller := caller sender ].
                "/ self log: 'caller is ', caller printString severity: INFO facility: 'STX' originator: self.

            ].
            i := i + 1.
        ].
    ].

    "/ Now check whether the severity is one of the predefined ones,
    "/ if not, issue an error
    (Severities includesIdentical: severityXlated) ifFalse:[ 
        | caller |
        self log: ('no such severity (%1), use one from predefined severities. Original message will be logged as INFO' bindWith: severityXlated) severity: ERROR facility: 'STX' originator: self.
        caller := thisContext sender.
        [ caller notNil and: [ caller receiver ~~ originator ] ] whileTrue:[ caller := caller sender ].
        self log: 'caller is ', caller printString severity: INFO facility: 'STX' originator: self.
        severityXlated := INFO.
    ].

    severityXlated value < Threshold value ifTrue:[ ^ self ].

    self log: message severity: severityXlated facility: facility originator: originator attachment: attachment on:Stderr.
    (Transcript isView) ifTrue:[ 
        self log: message severity: severityXlated facility: facility originator: originator attachment: attachment on:Transcript
    ].

    "
     Logger log:'test message' severity: #debug facility: 'TEST'
    "

    "Created: / 14-09-2011 / 21:18:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-08-2014 / 14:38:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 26-08-2014 / 09:37:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

log: message severity: severity originator: originator
    self log: message severity: severity facility: (self facilityOf: originator) originator: originator

    "Created: / 15-09-2011 / 10:26:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 15-03-2013 / 11:20:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MiniLogger class methodsFor:'logging - utils'!

debug: message
    DEBUG value < Threshold value ifTrue:[ ^ self ].
    self log: message severity: DEBUG
!

debug: format with: arg1
    DEBUG value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1) severity: DEBUG
!

debug: format with: arg1 with: arg2
    DEBUG value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1 with: arg2) severity: DEBUG
!

enter: message
    ENTER value < Threshold value ifTrue:[ ^ self ].
    self log: message severity: ENTER
!

enter: format with: arg1
    ENTER value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1) severity: ENTER
!

enter: format with: arg1 with: arg2
    ENTER value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1 with: arg2) severity: ENTER
!

error: message
    ERROR value < Threshold value ifTrue:[ ^ self ].
    self log: message severity: ERROR
!

error: format with: arg1
    ERROR value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1) severity: ERROR
!

error: format with: arg1 with: arg2
    ERROR value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1 with: arg2) severity: ERROR
!

fatal: message
    FATAL value < Threshold value ifTrue:[ ^ self ].
    self log: message severity: FATAL
!

fatal: format with: arg1
    FATAL value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1) severity: FATAL
!

fatal: format with: arg1 with: arg2
    FATAL value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1 with: arg2) severity: FATAL
!

info: message
    INFO value < Threshold value ifTrue:[ ^ self ].
    self log: message severity: INFO
!

info: format with: arg1
    INFO value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1) severity: INFO
!

info: format with: arg1 with: arg2
    INFO value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1 with: arg2) severity: INFO
!

leave: message
    LEAVE value < Threshold value ifTrue:[ ^ self ].
    self log: message severity: LEAVE
!

leave: format with: arg1
    LEAVE value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1) severity: LEAVE
!

leave: format with: arg1 with: arg2
    LEAVE value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1 with: arg2) severity: LEAVE
!

trace0: message
    TRACE0 value < Threshold value ifTrue:[ ^ self ].
    self log: message severity: TRACE0
!

trace0: format with: arg1
    TRACE0 value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1) severity: TRACE0
!

trace0: format with: arg1 with: arg2
    TRACE0 value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1 with: arg2) severity: TRACE0
!

trace1: message
    TRACE1 value < Threshold value ifTrue:[ ^ self ].
    self log: message severity: TRACE1
!

trace1: format with: arg1
    TRACE1 value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1) severity: TRACE1
!

trace1: format with: arg1 with: arg2
    TRACE1 value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1 with: arg2) severity: TRACE1
!

trace2: message
    TRACE2 value < Threshold value ifTrue:[ ^ self ].
    self log: message severity: TRACE2
!

trace2: format with: arg1
    TRACE2 value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1) severity: TRACE2
!

trace2: format with: arg1 with: arg2
    TRACE2 value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1 with: arg2) severity: TRACE2
!

trace3: message
    TRACE3 value < Threshold value ifTrue:[ ^ self ].
    self log: message severity: TRACE3
!

trace3: format with: arg1
    TRACE3 value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1) severity: TRACE3
!

trace3: format with: arg1 with: arg2
    TRACE3 value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1 with: arg2) severity: TRACE3
!

trace: message
    TRACE value < Threshold value ifTrue:[ ^ self ].
    self log: message severity: TRACE
!

trace: format with: arg1
    TRACE value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1) severity: TRACE
!

trace: format with: arg1 with: arg2
    TRACE value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1 with: arg2) severity: TRACE
!

warning: message
    WARNING value < Threshold value ifTrue:[ ^ self ].
    self log: message severity: WARNING
!

warning: format with: arg1
    WARNING value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1) severity: WARNING
!

warning: format with: arg1 with: arg2
    WARNING value < Threshold value ifTrue:[ ^ self ].
    self log: (format bindWith: arg1 with: arg2) severity: WARNING
! !

!MiniLogger class methodsFor:'private'!

facilityOf:originator 
    ^ originator class 
        perform:#logFacility
        ifNotUnderstood:[
            |pkg|

            pkg := originator class package.
            (pkg startsWith:'stx') ifTrue:[
                'STX'
            ] ifFalse:[
                pkg copyFrom:((pkg lastIndexOf:$:) + 1)
            ]
        ]

    "
     Logger facilityOf: Object
     Logger facilityOf: Expecco::Browser
    "

    "Created: / 15-09-2011 / 10:20:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

log: message severity: severity facility: facility originator: originator attachment: attachment on:aStream
    "Pricipal logging method. This mimics VM __stxLog__()"

    aStream
        nextPutAll: facility ? 'STX';
        space;
        nextPut:$[;
        nextPutAll: severity name;
        nextPut:$];
        space.

    aStream nextPut:$(.
    Timestamp now printOn:aStream format:'%(year)-%(mon)-%(day) %h:%m:%s'.
    aStream nextPut:$).
    aStream space.
    aStream nextPutAll: message.
    aStream cr.

    "
     Logger log:'test message' severity: #debug facility: 'TEST'
    "

    "Created: / 14-09-2011 / 21:18:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-08-2014 / 14:20:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MiniLogger::Severity methodsFor:'accessing'!

name
    ^ name
!

value
    ^ value
! !

!MiniLogger::Severity methodsFor:'initialization'!

initializeWithName: aString value: anInteger
    name := aString.
    value := anInteger

    "Created: / 13-08-2014 / 13:00:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MiniLogger::Severity methodsFor:'printing & storing'!

printOn:aStream
    "append a printed representation if the receiver to the argument, aStream"

    name printOn: aStream.

    "Modified: / 13-08-2014 / 13:46:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MiniLogger class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/MiniLogger.st,v 1.6 2014-08-26 08:43:40 vrany Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libbasic/MiniLogger.st,v 1.6 2014-08-26 08:43:40 vrany Exp $'
!

version_HG

    ^ '$Changeset: <not expanded> $'
!

version_SVN
    ^ '$Id: MiniLogger.st,v 1.6 2014-08-26 08:43:40 vrany Exp $'
! !


MiniLogger initialize!