PersistentFileHistory.st
author Claus Gittinger <cg@exept.de>
Sat, 02 May 2020 21:40:13 +0200
changeset 5476 7355a4b11cb6
parent 5059 c39053b76d96
permissions -rw-r--r--
#FEATURE by cg class: Socket class added: #newTCPclientToHost:port:domain:domainOrder:withTimeout: changed: #newTCPclientToHost:port:domain:withTimeout:

"
 COPYRIGHT (c) 2019 by Claus Gittinger
              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:libbasic2' }"

"{ NameSpace: Smalltalk }"

Object subclass:#PersistentFileHistory
	instanceVariableNames:'fileHistory fileHistorySizeLimit topDirectoryName applicationKey
		topRegistryKeyName'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-Framework'
!

PersistentFileHistory class instanceVariableNames:'fileHistory'

"
 No other class instance variables are inherited by this class.
"
!

!PersistentFileHistory class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2019 by Claus Gittinger
              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
"
    Support code tp provide a common access layer for persistent storage for applications.
    For example, a persistent history of previously opened files.
    On Windows systems, this is stored in the registry.
    On Unix systems, it is stored in the user's home folder under '.smalltalk/registry/...'.
    Both registry and directory use the same hierarchical structure.

    PersistentFileHistory new
        applicationKey:'GDBApplication';
        fileHistory
        
    [author:]
        Claus Gittinger
"
! !

!PersistentFileHistory class methodsFor:'instance creation'!

new
    "return an initialized instance"

    ^ self basicNew initialize.
! !

!PersistentFileHistory methodsFor:'accessing - configuration'!

applicationKey:aString
    "this is used as the key under which the application's values are stored.
     In the registry, this is the last key above the history entry);
     if files are used, this is the folder name above which history, and other files are stored.
     By default, the name of the application without prefix is used."

    applicationKey := aString.

    "Modified (comment): / 23-07-2019 / 17:33:49 / Claus Gittinger"
!

fileHistorySize
    "defines the number of remembered files in the history"

    ^ fileHistorySizeLimit ? 20.

    "Modified: / 23-07-2019 / 17:24:39 / Claus Gittinger"
!

fileHistorySizeLimit:something
    fileHistorySizeLimit := something.
!

topDirectoryName:topKeyName
    "defaults to '.smalltalk',
     but can be changed to '.expecco'."
     
    topDirectoryName := topKeyName.

    "Created: / 23-07-2019 / 17:22:16 / Claus Gittinger"
!

topRegistryKeyName:topKeyName
    "defaults to 'SmalltalkX',
     but can be changed to 'Expecco'."
     
    topRegistryKeyName := topKeyName.

    "Created: / 23-07-2019 / 17:25:27 / Claus Gittinger"
! !

!PersistentFileHistory methodsFor:'accessing - file history'!

addToFileHistory:aFilename
    "remember a filename in the file history"
    
    |fileHistory|

    fileHistory := self fileHistory.
    fileHistory synchronized:[
        fileHistory addFirst:aFilename asFilename.
        fileHistory size > self fileHistorySize ifTrue:[
            fileHistory removeLast.
        ].
        self makeFileHistoryPersistent
    ]

    "Modified: / 09-11-2010 / 16:07:14 / cg"
    "Modified (comment): / 29-10-2017 / 10:51:11 / cg"
    "Modified (comment): / 23-07-2019 / 17:47:17 / Claus Gittinger"
!

fileHistory
    "return the file history"
    
    fileHistory isNil ifTrue:[
        self initializeFileHistory
    ].
    ^ fileHistory

    "Modified (comment): / 23-07-2019 / 17:47:06 / Claus Gittinger"
!

fileHistoryFilteredForStillExistingFilesDo:aBlock removeNonExisting:aBoolean
    |history toRemove|

    toRemove := OrderedCollection new.

    history := self fileHistory.
    history notEmptyOrNil ifTrue:[
        history synchronized:[
            history do:[:aFilename|
                aFilename exists ifTrue:[
                    aBlock value:aFilename.               
                ] ifFalse:[
                    aBoolean ifTrue:[
                        toRemove add:aFilename.
                    ]
                ]
            ].
            aBoolean ifTrue:[
                "/ remove all non-existing history entries
                fileHistory removeAll:toRemove.
            ].
        ].
    ].

    "Created: / 29-10-2017 / 10:55:46 / cg"
    "Modified: / 23-07-2019 / 17:49:34 / Claus Gittinger"
! !

!PersistentFileHistory methodsFor:'file history support'!

registryKeyForApplication
    "HKEY_CURRENT_USER\Software\Exept\SmalltalkX\<appname>"

    |k_software k_exept k_stx k_app keyName|

    OperatingSystem isMSWINDOWSlike ifTrue:[
        keyName := applicationKey.

        k_software := Win32OperatingSystem registryEntry key:'HKEY_CURRENT_USER\Software\'.
        (k_exept := k_software subKeyNamed:'Exept') isNil ifTrue:[
            k_exept := k_software createSubKeyNamed:'Exept'
        ].
        (k_stx := k_exept subKeyNamed:topRegistryKeyName) isNil ifTrue:[
            k_stx := k_exept createSubKeyNamed:topRegistryKeyName
        ].
        (k_app := k_stx subKeyNamed:keyName) isNil ifTrue:[
            k_app := k_stx createSubKeyNamed:keyName
        ].
        ^ k_app
    ].

    ^ nil

    "
     self registryKeyForApplication 
    "

    "Created: / 11-01-2011 / 19:58:26 / cg"
    "Modified: / 24-07-2019 / 08:30:34 / Claus Gittinger"
!

registryKeyForFileHistory
    "HKEY_CURRENT_USER\Software\Exept\SmalltalkX\<appName>\History"

    |k_app k_history|

    OperatingSystem isMSWINDOWSlike ifTrue:[
        k_app := self registryKeyForApplication.
        (k_history := k_app subKeyNamed:'History') isNil ifTrue:[
            k_history := k_app createSubKeyNamed:'History'
        ].
        ^ k_history
    ].

    ^ nil

    "
     self registryKeyForFileHistory
    "
! !

!PersistentFileHistory methodsFor:'initialization'!

initialize
    "can be set to '.expecco'"
    topDirectoryName := '.smalltalk'.
    topRegistryKeyName := 'SmalltalkX'.
    fileHistorySizeLimit := 25.

    "Created: / 23-07-2019 / 17:21:27 / Claus Gittinger"
! !

!PersistentFileHistory methodsFor:'private'!

directoryForFileHistory
    "the filename where the history is made persistent.
     This depends on the owningApplication which should not be nil."

    ^ Filename homeDirectory / topDirectoryName / applicationKey

    "
     self new directoryForFileHistory
    "

    "Modified (comment): / 29-10-2017 / 10:51:29 / cg"
    "Modified: / 23-07-2019 / 17:45:22 / Claus Gittinger"
!

fetchFileHistoryFromPersistentStore
    |k index value dir fn|

    fileHistory := OrderedSet new.

    OperatingSystem isMSWINDOWSlike ifTrue:[
        k := self registryKeyForFileHistory.
        index := 1.
        [
            value := k valueNamed:(index printString).
            value notNil
        ] whileTrue:[
            fileHistory add:value asFilename.
            index := index + 1
        ].
        k close.
    ] ifFalse:[
        dir := self directoryForFileHistory.
        dir isDirectory ifTrue:[
            fn := dir / 'history'.
            fn exists ifTrue:[
                fileHistory addAll:(fn contents collect:[:s | s asFilename])
            ]
        ]
    ]

    "Modified: / 16-05-2019 / 19:05:49 / Stefan Vogel"
    "Modified: / 23-07-2019 / 17:20:08 / Claus Gittinger"
!

initializeFileHistory
    fileHistory := OrderedSet new.
    self fetchFileHistoryFromPersistentStore.
!

makeFileHistoryPersistent
    |k index dir fn|

    OperatingSystem isMSWINDOWSlike ifTrue:[
        k := self registryKeyForFileHistory.
        fileHistory doWithIndex:[:filePath :index |
            k valueNamed:(index printString) put:filePath asFilename pathName.
        ].

        "/ remove the remaining keys
        index := fileHistory size + 1.
        [
            k deleteValueNamed:(index printString)
        ] whileTrue:[
            index := index + 1
        ].
    ] ifFalse:[
        (dir := self directoryForFileHistory) exists ifFalse:[
            dir recursiveMakeDirectory
        ].
        fn := dir / 'history'.
        fn contents:(fileHistory collect:[:fn | fn pathName]).
    ]
! !

!PersistentFileHistory class methodsFor:'documentation'!

version_CVS
    ^ '$Header$'
! !