MiniLogger.st
author convert-repo
Thu, 05 Jul 2018 03:33:35 +0000
changeset 23197 823c765c176d
parent 23148 0c8e169a2e11
child 23200 43417d0ac3f2
permissions -rw-r--r--
update tags

"{ Encoding: utf8 }"

"
 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' }"

"{ NameSpace: Smalltalk }"

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

Magnitude 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.
"
!

documentation
"
    A very simple logger for Smalltalk/X. This one is always present.
    It mimics the protocol of the loggers found in stx:goodies/loggia,
    which can be activated by setting the global 'Logger' to an instance of
    one of them.

    All
        'Transcript show: 'Processor [info]: xxx'
    should be rewritten over time to use the Logger.

    'Object infoPrint' and 'Object debugPrint' have been changed to
    forward their messages to the global 'Logger' if not nil.

    Usage:
        Logger info: 'Hello world'.
        Logger debug: 'Hello world'.
        Logger warning: 'Hello world'.
        Logger error: 'Hello world'.

    to disable logging:
        MiniLogger logOnTranscript:false.
        MiniLogger logOnStderr:false.

    for selective logging:
        Logger loggingThreshold: Logger severityALL.
        Logger loggingThreshold: Logger severityINFO.
        Logger loggingThreshold: Logger severityNONE.

    The following keywords are expanded in the message:
        'LINE'      linenumber in the sending method
        'RECEIVER'  printstring of receiver in sending context
        'CLASS'     class of receiver in sending context
        'MCLASS'    class of sendig method
        'SELECTOR'  selector of sending method
        'WHO'       who-string of sending method
        'WHERE'     who-string plus linenumber of sending method

    i.e.
        Logger info:'%(WHERE) - some message here'

    For more examples, see #examples.

    [author:]
        Jan Vrany <jan.vrany@fit.cvut.cz>

    [instance variables:]

    [class variables:]

    [see also:]
        Loggia logging framework (stx:goodies/loggia)
"
!

examples
"
    Simple logging (make sure logging threshold is lower or equal then
    Logger severityDEBUG, see #loggingThreshold:)
                                                                        [exBegin]
        Logger debug: 'Hello world!!'
                                                                        [exEnd]


    You may use #<severity>:with:with: utility to format log message:
                                                                        [exBegin]
        |hostname port|

        hostname := 'www.google.com'.
        port := 80.
        Logger error: 'Cannot connect to %1 port %2' with: hostname with: port
                                                                        [exEnd]

    and even automatically include a lineNumber:
                                                                        [exBegin]
        Logger info: '[%(CLASS)>>%(SELECTOR):%(LINE)] Hello world!!'
                                                                        [exEnd]


"
! !

!MiniLogger class methodsFor:'initialization'!

initialize
    LogOnStderr := true.
    LogOnTranscript := true.

    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.
    WARNING := Severity new initializeWithName:#warning value:88.
    ERROR := Severity new initializeWithName:#error value:99.
    FATAL := Severity new initializeWithName:#fatal value:100.
    NONE := Severity new initializeWithName:#none value:65535.

    Severities := {ENTER. LEAVE. TRACE3. TRACE2. TRACE1. TRACE0. TRACE. DEBUG. INFO. WARN. WARNING. ERROR. FATAL.}.
    Threshold := InfoPrinting ifTrue:[INFO] ifFalse:[WARN].

    (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-log format'!

logFormat
    "will be used for the log message as:
        %1 [%2] (%3): %4
    with %1: facility (area)
    with %2: secerity (area)
    with %3: timestamp 
    with %4: caller/originator 
    with %5: message"
    
    ^ LogFormat ? '%1 [%2] (%3): %5'

    "
     MiniLogger logFormat:'%1 [%2]: %5'.
     'hello' errorPrintCR.
     MiniLogger logFormat:'%3 %1 [%2]: %5'.
     'hello' errorPrintCR.
     MiniLogger logFormat:nil.
     'hello' errorPrintCR.
    "
!

logFormat:aFormatString
    "will be used for the log message as:
        %1 [%2] (%3): %4
            with %1: facility (area)
            with %2: secerity (area)
            with %3: timestamp 
            with %4: caller/originator 
            with %5: message.
     Pass anil argument to return to the default format.        
    "
    
    LogFormat := aFormatString

    "
     MiniLogger logFormat:'%1 [%2]: %5'.
     'hello' errorPrintCR.
     MiniLogger logFormat:'%3 %1 [%2]: %5'.
     'hello' errorPrintCR.
     MiniLogger logFormat:nil.
     'hello' errorPrintCR.
    "
!

logOnStderr 
    ^ LogOnStderr
!

logOnStderr:aBoolean
    "enable/disable logging on stderr"

    LogOnStderr := aBoolean

    "
     MiniLogger logOnStderr:false
     MiniLogger logOnTranscript:false

     MiniLogger logOnStderr:true
     MiniLogger logOnTranscript:true
    "

    "Modified (comment): / 25-01-2018 / 12:13:53 / mawalch"
!

logOnTranscript
    ^ LogOnTranscript 
!

logOnTranscript:aBoolean
    "enable/disable logging on the Transcript"

    LogOnTranscript := aBoolean

    "
     MiniLogger logOnStderr:false
     MiniLogger logOnTranscript:false

     MiniLogger logOnStderr:true
     MiniLogger logOnTranscript:true
    "

    "Modified (comment): / 25-01-2018 / 12:13:36 / mawalch"
!

timestampFormat
    "will be used for the log message"
    
    ^ TimestampFormat ? '%(year)-%(mon)-%(day) %h:%m:%s.%i'.
!

timestampFormat:aTimestampFormatString
    "will be used for the log message"
    
    TimestampFormat := aTimestampFormatString
! !

!MiniLogger class methodsFor:'accessing-severities'!

severities
    ^ 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.
     The default is 
        InfoPrinting ifTrue:[INFO] ifFalse:[WARN]
     meaning that by default, no trace and debug logs are generated."
    
    ^ Threshold

    "
     self loggingThreshold:INFO.
     self trace:'blabla'.
     self loggingThreshold:TRACE.
     self trace:'blabla'.
     self loggingThreshold:INFO.
    "

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

loggingThreshold:severity 
    "Sets logging threshold. 
     All severities higher or equal to the 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

    "
    Logger loggingThreshold: Logger severityALL.
    Logger loggingThreshold: Logger severityINFO.
    Logger loggingThreshold: Logger severityDEBUG.
    
    Logger loggingThreshold: Logger severityNONE.
    "

    "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>"
    "Modified (comment): / 09-10-2014 / 09:35:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 01-03-2017 / 10:42:31 / cg"
!

loggingThreshold:aLimitOrNil forClass:aClass
    "allows individual per-class setting of the threshold (useful during debugging).
     With a nil limit, the default is reinstalled for that class."

    "/ the original scheme asked the class;
    "/ but that required adding a getter to debugged classes, which
    "/ is easily forgotten and checked in.
    "/ Better keep that nfo here, so wemight even provide a GUI for it some time in the future...

    "/ remember the class name - in case it is reloaded/changes identity etc.
    aLimitOrNil isNil ifTrue:[
        ThresholdPerClass notNil ifTrue:[
            ThresholdPerClass removeKey:(aClass theNonMetaclass name) ifAbsent:[].
            ThresholdPerClass isEmpty ifTrue:[
                ThresholdPerClass := nil.
            ].
        ].
        ^ self
    ].    
    ThresholdPerClass isNil ifTrue:[
        ThresholdPerClass := Dictionary new.
    ].
    ThresholdPerClass at:aClass theNonMetaclass name put:aLimitOrNil.

    "
     Logger severityThresholdOf: Object
     Logger severityThresholdOf: Expecco::Browser

     Logger loggingThreshold:(Logger severityDEBUG) forClass:(Expecco::Browser).
     Logger loggingThreshold:(Logger severityDEBUG) forPackage:'stx:libbasic'.
     Logger loggingThreshold:(Logger severityDEBUG) forPackage:'exept:workflow'.

     Logger loggingThreshold:nil forClass:(Expecco::Browser).
     Logger loggingThreshold:nil forPackage:'stx:libbasic'.
    "

    "Created: / 01-03-2017 / 10:52:25 / cg"
!

loggingThreshold:aLimitOrNil forPackage:aPackageName
    "allows individual per-package setting of the threshold (useful during debugging).
     With a nil limit, the default is reinstalled for that class."

    "/ the original scheme only asked the class;
    "/ but that required adding many getters to debugged packages, 
    "/ which are easily forgotten and checked in.
    "/ Better keep that info here, so we might even provide a GUI for it some time in the future...

    "/ remember the class name - in case it is reloaded/changes identity etc.
    aLimitOrNil isNil ifTrue:[
        ThresholdPerPackage notNil ifTrue:[
            ThresholdPerPackage removeKey:(aPackageName) ifAbsent:[].
            ThresholdPerPackage isEmpty ifTrue:[
                ThresholdPerPackage := nil.
            ].
        ].
        ^ self
    ].    
    ThresholdPerPackage isNil ifTrue:[
        ThresholdPerPackage := Dictionary new.
    ].
    ThresholdPerPackage at:aPackageName put:aLimitOrNil.

    "
     Logger severityThresholdOf: Object
     Logger severityThresholdOf: Expecco::Browser

     Logger loggingThreshold:(Logger severityDEBUG) forClass:(Expecco::Browser).
     Logger loggingThreshold:(Logger severityDEBUG) forPackage:'stx:libbasic'.
     Logger loggingThreshold:(Logger severityDEBUG) forPackage:'exept:workflow'.

     Logger loggingThreshold:nil forClass:(Expecco::Browser).
     Logger loggingThreshold:nil forPackage:'stx:libbasic'.
    "

    "Created: / 01-03-2017 / 10:53:42 / cg"
! !

!MiniLogger class methodsFor:'logging'!

log: message
    self log:message severity:DEBUG originator:(thisContext sender receiver).

    "Created: / 15-09-2011 / 10:27:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 02-12-2014 / 10:52:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 01-03-2017 / 10:27:52 / cg"
!

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

    "Created: / 14-09-2011 / 21:22:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 02-12-2014 / 10:53:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

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

    "Created: / 15-09-2011 / 10:25:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 02-12-2014 / 10:53:11 / 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:facilityArg originator:originator attachment:attachment
    "Pricipal logging method. This mimics VM __stxLog__()"

    | severityXlated messageXlated prevLogOnTranscript facility severityName words secondWord|

    (self canLog) ifFalse:[^ self].

    severityXlated := severity.

    severityXlated isSymbol ifTrue:[
        "/ Be backward compatible, allow for symbolic severities
        "/ but when encountered, issue a warning...
        severityXlated := Severities detect:[:each| each name == severityXlated] ifNone:[].

        "/ 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.
    ] ifFalse:[
       "/ Now check whether the severity is one of the predefined ones,
        "/ if not, issue an error
        (Severities includesIdentical:severityXlated) ifFalse:[ 
            | caller |

            caller := thisContext sender.
            [caller notNil and:[caller receiver ~~ originator]] whileTrue:[ 
                caller := caller sender
            ].
            self log:('no such severity (%1, called from %2), use one from predefined severities. Original message will be logged as INFO' bindWith:severityXlated with:caller) 
                 severity: ERROR facility: 'STX' originator: self.
            severityXlated := INFO.
        ].
    ].

    messageXlated := message value asString.
    facility := facilityArg.

    "/ hack to allow calls from #infoPrint/#errorPrint.
    "/ if this is an oldStyle #infoPrint or #errorPrint, do not append another facility and severity
    words := messageXlated asCollectionOfWords.
    (words size >= 2
     and:[words first isAlphaNumeric
     and:[((secondWord := words second) startsWith:$[ )
     and:[(secondWord endsWith:$]) or:[(secondWord endsWith:']:')]]]]) ifTrue:[
        facility := words first.
        severityName := secondWord copyFrom:2 to:(secondWord indexOf:$])-1.
        severityXlated := Severities detect:[:each| each name = severityName] 
                                     ifNone:[Severity new initializeWithName:severityName value:severity value].

        messageXlated := messageXlated copyFrom:(messageXlated indexOf:$])+1.
        (messageXlated startsWith:$:) ifTrue:[
            messageXlated := messageXlated copyFrom:2.
        ].
        (messageXlated startsWith:Character space) ifTrue:[
            messageXlated := messageXlated copyFrom:2.
        ].
    ].

    "/ a quick rejector to avoid overhead in deployed apps
    (ThresholdPerClass isNil and:[ThresholdPerPackage isNil]) ifTrue:[
        (Threshold > severityXlated) ifTrue:[ ^ self ].
    ] ifFalse:[
        ((self severityThresholdOf:originator) > severityXlated) ifTrue:[^ self ].  
    ].
    
    thisContext isRecursive ifTrue:[
        'STX:Logger [error]: recursive logger invocation.' _errorPrintCR.
        ^ self.
    ].

    "/ to avoid recursion, turn off logOnTranscript while logging
    "/ had this problem with RecursionLock, which wanted to issue a warning
    "/ ("cleanup for dead process") from inside Transcript code.
    prevLogOnTranscript := LogOnTranscript.
    [
        LogOnTranscript := false.
        
        self basicLog:messageXlated severity:severityXlated facility:facility 
             originator:originator attachment:attachment.

        (prevLogOnTranscript and:[Transcript isView]) ifTrue:[
            Transcript nextPutLine:messageXlated.
        ].
    ] ensure:[
        LogOnTranscript := prevLogOnTranscript.
    ].
    
    "
     Logger log:'test message' severity:self severityINFO facility: 'TEST'
     Logger log:'test message' severity:#info facility: 'TEST'
     Logger log:'test message' severity:#bla facility: 'TEST'
     Logger log:'test message' severity:123 facility: 'TEST'

     Logger log:'test message' severity: DEBUG facility: 'TEST'
     Logger log:'test message' severity: INFO facility: 'TEST'
     Logger log:'test message' asUnicode16String severity: INFO facility: 'TEST'
     Logger log:'test message äöüß' severity: INFO facility: 'TEST'
     Logger log:'test message' severity: WARNING facility: 'TEST'
     Logger log:'test message' severity: ERROR facility: 'TEST'
     'test message' infoPrintCR
     'test message' errorPrintCR
    "

    "backward compatibility with infoPrint/errorPrint callers:
     'foo [info] test message' infoPrintCR
     'bar [error] test message' errorPrintCR
     'foo [info]: test message' infoPrintCR
     'bar [error]: test message' errorPrintCR
    "

    "Created: / 14-09-2011 / 21:18:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 20-01-2015 / 18:40:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 01-03-2017 / 11:15:46 / cg"
    "Modified: / 28-06-2018 / 11:15:42 / Stefan Vogel"
!

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
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > DEBUG) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log:(self expand:message) severity: DEBUG originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:54:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:32:39 / cg"
!

debug: format with: arg1
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > DEBUG) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log:(self expand:format with: arg1) severity:DEBUG originator:(thisContext sender receiver)

    "Modified: / 02-12-2014 / 10:54:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 13-03-2017 / 15:37:47 / cg"
!

debug: format with: arg1 with: arg2
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > DEBUG) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2) severity: DEBUG originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:54:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:39:04 / cg"
!

debug:format with:arg1 with:arg2 with:arg3
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > DEBUG) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2 with:arg3) severity: DEBUG originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:54:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:41:26 / cg"
!

enter:message
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > ENTER) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log:(self expand:message) severity:ENTER originator:(thisContext sender receiver)

    "Modified: / 02-12-2014 / 10:54:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:35:15 / cg"
!

enter: format with: arg1
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > ENTER) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with: arg1) severity: ENTER originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:54:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:37:51 / cg"
!

enter: format with: arg1 with: arg2
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > ENTER) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2) severity: ENTER originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:54:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:39:07 / cg"
!

enter: format with: arg1 with: arg2 with:arg3
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > ENTER) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2 with:arg3) severity: ENTER originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:54:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:41:32 / cg"
!

error: message
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > ERROR) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log:(self expand:message) severity:ERROR originator:(thisContext sender receiver)

    "Modified: / 02-12-2014 / 10:54:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:35:29 / cg"
!

error: format with: arg1
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > ERROR) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with: arg1) severity: ERROR originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:54:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:37:55 / cg"
!

error: format with: arg1 with: arg2
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > ERROR) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2) severity: ERROR originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:54:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:39:12 / cg"
!

error: format with: arg1 with: arg2 with:arg3
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > ERROR) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2 with:arg3) severity: ERROR originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:54:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:41:37 / cg"
!

fatal: message
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > FATAL) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log:(self expand:message) severity:FATAL originator:(thisContext sender receiver)

    "Modified: / 02-12-2014 / 10:54:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:35:41 / cg"
!

fatal: format with: arg1
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > FATAL) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with: arg1) severity: FATAL originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:54:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:37:58 / cg"
!

fatal: format with: arg1 with: arg2
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > FATAL) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2) severity: FATAL originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:54:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:40:17 / cg"
!

fatal: format with: arg1 with: arg2 with:arg3
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > FATAL) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].
    
    self log: (self expand:format with:arg1 with:arg2 with:arg3) severity: FATAL originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:54:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:41:40 / cg"
!

info: message
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > INFO) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log:(self expand:message) severity:INFO originator:(thisContext sender receiver)

    "Modified: / 02-12-2014 / 10:55:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:35:51 / cg"
!

info: format with: arg1
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > INFO) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with: arg1) severity: INFO originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:55:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:38:01 / cg"
!

info: format with: arg1 with: arg2
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > INFO) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2) severity: INFO originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:55:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:40:26 / cg"
!

info: format with: arg1 with: arg2 with:arg3
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > INFO) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2 with:arg3) severity: INFO originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:55:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:41:43 / cg"
!

leave: message
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > LEAVE) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log:(self expand:message) severity:LEAVE originator:(thisContext sender receiver)

    "Modified: / 02-12-2014 / 10:55:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:36:02 / cg"
!

leave: format with: arg1
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > LEAVE) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with: arg1) severity: LEAVE originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:55:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:38:05 / cg"
!

leave: format with: arg1 with: arg2
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > LEAVE) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2) severity: LEAVE originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:55:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:40:32 / cg"
!

leave: format with: arg1 with: arg2 with:arg3
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > LEAVE) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2 with:arg3) severity: LEAVE originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:55:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:42:06 / cg"
!

trace0: message
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > TRACE0) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log:(self expand:message) severity:TRACE0 originator:(thisContext sender receiver)

    "Modified: / 02-12-2014 / 10:55:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:36:15 / cg"
!

trace0: format with: arg1
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > TRACE0) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with: arg1) severity: TRACE0 originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:55:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:38:09 / cg"
!

trace0: format with: arg1 with: arg2
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > TRACE0) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2) severity: TRACE0 originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:55:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:40:35 / cg"
!

trace0: format with: arg1 with: arg2 with:arg3
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > TRACE0) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2 with:arg3) severity: TRACE0 originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:55:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:42:09 / cg"
!

trace1: message
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > TRACE1) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log:(self expand:message) severity:TRACE1 originator:(thisContext sender receiver)

    "Modified: / 02-12-2014 / 10:55:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:36:26 / cg"
!

trace1: format with: arg1
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > TRACE1) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with: arg1) severity: TRACE1 originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:55:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:38:13 / cg"
!

trace1: format with: arg1 with: arg2
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > TRACE1) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2) severity: TRACE1 originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:55:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:40:40 / cg"
!

trace1: format with: arg1 with: arg2 with:arg3
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > TRACE1) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2 with:arg3) severity: TRACE1 originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:55:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:42:14 / cg"
!

trace2: message
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > TRACE2) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log:(self expand:message) severity:TRACE2 originator:(thisContext sender receiver)

    "Modified: / 02-12-2014 / 10:55:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:36:34 / cg"
!

trace2: format with: arg1
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > TRACE2) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with: arg1) severity: TRACE2 originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:55:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:38:17 / cg"
!

trace2: format with: arg1 with: arg2
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > TRACE2) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2) severity: TRACE2 originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:55:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:40:43 / cg"
!

trace2: format with: arg1 with: arg2 with:arg3
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > TRACE2) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2 with:arg3) severity: TRACE2 originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:55:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:42:17 / cg"
!

trace3: message
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > TRACE3) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log:(self expand:message) severity:TRACE3 originator:(thisContext sender receiver)

    "Modified: / 02-12-2014 / 10:55:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:36:47 / cg"
!

trace3: format with: arg1
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > TRACE3) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with: arg1) severity: TRACE3 originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:55:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:38:19 / cg"
!

trace3: format with: arg1 with: arg2
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > TRACE3) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2) severity: TRACE3 originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:56:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:40:47 / cg"
!

trace3: format with: arg1 with: arg2 with:arg3
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > TRACE3) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2 with:arg3) severity: TRACE3 originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:56:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:42:20 / cg"
!

trace: message
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > TRACE) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log:(self expand:message) severity:TRACE originator:(thisContext sender receiver)

    "Modified: / 02-12-2014 / 10:56:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:36:55 / cg"
!

trace: format with: arg1
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > TRACE) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log:(self expand:format with: arg1) severity: TRACE originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:56:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:38:29 / cg"
!

trace: format with: arg1 with: arg2
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > TRACE) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2) severity: TRACE originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:56:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:40:51 / cg"
!

trace: format with: arg1 with: arg2 with:arg3
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > TRACE) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2 with:arg3) severity: TRACE originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:56:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:42:24 / cg"
!

warning: message
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > WARN) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log:(self expand:message) severity:WARN originator:(thisContext sender receiver)

    "Modified: / 02-12-2014 / 10:56:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:37:05 / cg"
!

warning: format with: arg1
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > WARN) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with: arg1) severity: WARN originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:56:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:38:31 / cg"
!

warning:format with:arg1 with:arg2
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > WARN) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2) severity: WARN originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:56:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:40:54 / cg"
!

warning:format with:arg1 with:arg2 with:arg3
    "/ a quick rejector to avoid overhead in deployed apps
    ((Threshold > WARN) and:[ThresholdPerClass isNil and:[ThresholdPerPackage isNil]]) ifTrue:[ ^ self ].

    self log: (self expand:format with:arg1 with:arg2 with:arg3) severity: WARN originator: thisContext sender receiver

    "Modified: / 02-12-2014 / 10:56:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-03-2017 / 15:42:27 / cg"
! !

!MiniLogger class methodsFor:'private'!

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

    |messageAsSent|

    (LogOnStderr not or:[Stderr isNil]) ifFalse:[
        ^ self.
    ].

    messageAsSent := 
            self logFormat
                bindWith:(facility ? 'STX')
                with:severity name
                with:(Timestamp now printStringFormat:(self timestampFormat))
                with:originator
                with:message.

    "/ If the message is Unicode 16/32 string and stream is external,
    "/ we have to recode the message using locale-specific encoding
    Stderr isExternalStream ifTrue:[
        messageAsSent := messageAsSent string.  "take care of Texts"
        messageAsSent containsNon7BitAscii ifTrue:[
            OperatingSystem isMSWINDOWSlike ifTrue:[
                messageAsSent := messageAsSent utf8Encoded.
            ] ifFalse:[
                messageAsSent := OperatingSystem encodePath:messageAsSent.
            ].
        ].
        [
            Stderr nextPutLine: messageAsSent
        ] on:StreamError do:[:ex|
            'STX:Logger [error]: error writing to stream: ' _errorPrint.
            ex description _errorPrintCR.
            messageAsSent _errorPrintCR.
        ].
        ^ self.
    ].

    Stderr nextPutLine: messageAsSent

    "Created: / 28-06-2018 / 11:05:17 / Stefan Vogel"
!

expand:message
    |d|

    d := Dictionary new.
    ^ self expand:message addingInfoFrom:(thisContext sender sender) to:d

    "Created: / 13-03-2017 / 15:34:47 / cg"
!

expand:message addingInfoFrom:aContext to:aDictionary
    |messageString mthd rcvr methodWho|
    
    (messageString := message) isString ifFalse:[
        messageString := message value asString.
        messageString isString ifFalse:[ ^ messageString asString].
    ].

    mthd := aContext method.
    rcvr := aContext receiver.
    methodWho := mthd whoString.
    
    aDictionary at:'LINE' put:(aContext lineNumber).
    aDictionary at:'RECEIVER' put:(rcvr displayString).
    aDictionary at:'CLASS' put:(rcvr class).
    aDictionary at:'MCLASS' put:(mthd mclass).
    aDictionary at:'SELECTOR' put:(mthd selector).
    aDictionary at:'WHO' put:methodWho.
    aDictionary at:'WHERE' put:(methodWho,'@',aContext lineNumber printString).
    ^ messageString expandPlaceholdersWith:aDictionary

    "Created: / 13-03-2017 / 15:46:52 / cg"
    "Modified: / 03-05-2017 / 15:38:35 / cg"
!

expand:message with:arg1
    |d|

    d := Dictionary new.
    d at:1 put:arg1.
    ^ self expand:message addingInfoFrom:(thisContext sender sender) to:d

    "Created: / 13-03-2017 / 15:37:25 / cg"
!

expand:message with:arg1 with:arg2
    |d|

    d := Dictionary new.
    d at:1 put:arg1.
    d at:2 put:arg2.
    ^ self expand:message addingInfoFrom:(thisContext sender sender) to:d

    "Created: / 13-03-2017 / 15:38:50 / cg"
!

expand:message with:arg1 with:arg2 with:arg3
    |d|

    d := Dictionary new.
    d at:1 put:arg1.
    d at:2 put:arg2.
    d at:3 put:arg3.
    ^ self expand:message addingInfoFrom:(thisContext sender sender) to:d

    "Created: / 13-03-2017 / 15:41:05 / cg"
!

facilityOf:originator 
    ^ originator class logFacility
"/    ^ 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>"
    "Modified: / 01-03-2017 / 10:43:23 / cg"
!

severityThresholdOf:originator
    "allow each class to define an individual threshold for Logging"

    |cls t|

    cls := originator class.
    ThresholdPerClass notNil ifTrue:[
        t := ThresholdPerClass at:(cls theNonMetaclass name) ifAbsent:nil.
        t notNil ifTrue:[^ t].
    ].
    ThresholdPerPackage notNil ifTrue:[
        t := ThresholdPerPackage at:(cls package) ifAbsent:nil.
        t notNil ifTrue:[^ t].
    ].

    "/ disabled; the above scheme is better...
    "/ ^ cls 
    "/    perform:#logSeverityThreshold
    "/     ifNotUnderstood:[ ^ Threshold ]
    ^ Threshold
    
    "
     Logger severityThresholdOf: Object
     Logger severityThresholdOf: Expecco::Browser

     Logger loggingThreshold:(Logger severityDEBUG) forClass:(Expecco::Browser).
     Logger loggingThreshold:(Logger severityDEBUG) forPackage:'stx:libbasic'.

     Logger loggingThreshold:nil forClass:(Expecco::Browser).
     Logger loggingThreshold:nil forPackage:'stx:libbasic'.
    "

    "Created: / 15-09-2011 / 10:20:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 01-03-2017 / 10:59:12 / cg"
! !

!MiniLogger class methodsFor:'queries'!

canLog
    "answer true, if logging can be performed. Subclasse may redefine this."

    ^ (LogOnStderr and:[Stderr notNil])
       or:[LogOnTranscript and:[Transcript isView]].

    "Created: / 28-06-2018 / 10:47:29 / Stefan Vogel"
! !

!MiniLogger::Severity methodsFor:'accessing'!

name
    ^ name
!

value
    ^ value
! !

!MiniLogger::Severity methodsFor:'arithmetic'!

+ aNumber
    |next|

    next := value + aNumber.
    aNumber negative ifTrue:[
        ^ MiniLogger severities detectLast:[:each| each = next or:[each < next]] ifNone:[self class new initializeWithName:#nil value:next]
    ].

    ^ MiniLogger severities detect:[:each| each >= next] ifNone:[self class new initializeWithName:#nil value:next]

    "
        MiniLogger severityINFO + 1
        MiniLogger severityTRACE to:MiniLogger severityFATAL do:[:each| Transcript showCR:each].
        MiniLogger severityFATAL downTo:MiniLogger severityTRACE do:[:each| Transcript showCR:each].
    "
! !

!MiniLogger::Severity methodsFor:'comparing'!

< aSeverity
    ^ value < aSeverity value
!

= aSeverity
    ^ self == aSeverity or:[value = aSeverity value]
!

hash
    "instances, for which #= answers true must answer the same hash"

    ^ value hash
! !

!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 of 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$'
!

version_CVS
    ^ '$Header$'
!

version_HG

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

version_SVN
    ^ '$Id$'
! !


MiniLogger initialize!