MiniLogger.st
author convert-repo
Thu, 14 Aug 2014 21:15:03 +0000
changeset 16820 20cf88fba119
parent 16784 05fdf667949e
child 16826 a7fd70258cef
permissions -rw-r--r--
update tags

"
 COPYRIGHT (c) 2006 by 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:'Instance'
	poolDictionaries:''
	category:'System-Debugging-Support'
!

!MiniLogger class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2006 by 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:'instance creation'!

instance
    Instance isNil ifTrue:[Instance := self basicNew].
    ^Instance

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

new
    Logger log: 'Do not use MiniLogger new, use #instance instead' severity: #warn facility: 'STX'.
    ^self instance

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

!MiniLogger class methodsFor:'class initialization'!

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

    "Created: / 01-09-2011 / 12:26:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MiniLogger methodsFor:'logging'!

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
    self log: message severity: #debug

    "Created: / 15-09-2011 / 10:27:46 / 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>"
!

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

    "Created: / 15-09-2011 / 10:25:58 / 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>"
!

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__()"

    self log: message severity: severity facility: facility originator: originator attachment: attachment on:Stderr.
    Transcript ~~ Stderr ifTrue:[ 
        self log: message severity: severity 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>"
!

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;
        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>"
!

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:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/MiniLogger.st,v 1.5 2014-07-18 15:27:03 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libbasic/MiniLogger.st,v 1.5 2014-07-18 15:27:03 cg Exp $'
!

version_HG

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

version_SVN
    ^ '$Id: MiniLogger.st,v 1.5 2014-07-18 15:27:03 cg Exp $'
! !


MiniLogger initialize!