BookmarkList.st
author Claus Gittinger <cg@exept.de>
Fri, 01 Jul 2011 15:30:32 +0200
changeset 9998 dc88261b0fc2
parent 9972 1a82b2155085
child 10085 d965c17bd9c4
permissions -rw-r--r--
initial checkin

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

HierarchicalList subclass:#BookmarkList
	instanceVariableNames:'fileName'
	classVariableNames:'BrowserBookmarks WorkspaceBookmarks WebBookmarks'
	poolDictionaries:''
	category:'Interface-Bookmarks'
!

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

!BookmarkList class methodsFor:'instance creation'!

decodeFromLiteralArray:anArray

    (anArray size == 3 and: [anArray second == #root:]) ifFalse:
        [self breakPoint: #jv. ^super decodeFromLiteralArray:anArray].

    ^self new root: anArray third decodeAsLiteralArray

    "Created: / 23-05-2011 / 14:28:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

new
    "return an initialized instance"

    ^ super new initialize.

    "Modified: / 23-05-2011 / 13:57:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

readFrom: aStream onError: aBlock

    | litArray |
    ^[
        litArray := Compiler evaluate: aStream contents asString.
        litArray decodeAsLiteralArray.
    ] on: Error do: [
        aBlock value.
        nil
    ]

    "Created: / 23-05-2011 / 15:58:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

readFromFile: aStringOrFilename

    | bookmarks file |
    file := aStringOrFilename asFilename.
    file exists ifFalse:
        [self error: ('File does %1 not exists' bindWith: file pathName)].
    bookmarks := self readFrom: file readStream onError: 
        [self error: ('Cannot parse %1 not exists' bindWith: file pathName)].
    bookmarks fileName: file pathName.
    ^bookmarks

    "Created: / 23-05-2011 / 16:10:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

readFromFile: aStringOrFilename onError: aBlock

    | bookmarks file |
    file := aStringOrFilename asFilename.
    file exists ifFalse:
        [^aBlock value].
    bookmarks := self readFrom: file readStream onError: 
        [^aBlock value].
    bookmarks ifNil:
        [^aBlock value].
    bookmarks fileName: file pathName.
    ^bookmarks

    "Created: / 23-05-2011 / 16:32:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 02-06-2011 / 19:43:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!BookmarkList class methodsFor:'accessing'!

forSystemBrowser

    BrowserBookmarks isNil ifTrue:
        [self initializeBrowserBookmarks].
    ^BrowserBookmarks

    "Created: / 23-05-2011 / 10:10:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

forWebBrowser

    WebBookmarks isNil ifTrue:
        [self initializeWebBookmarks].
    ^WebBookmarks

    "Created: / 08-06-2011 / 12:15:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

forWorkspace

    WorkspaceBookmarks isNil ifTrue:
        [self initializeWorkspaceBookmarks].
    ^WorkspaceBookmarks

    "Created: / 20-06-2011 / 22:11:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!BookmarkList class methodsFor:'accessing - defaults'!

defaultLabelForMyWorkspaces

    ^'My Workspaces'

    "Created: / 21-06-2011 / 08:35:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

defaultLabelForRecent

    ^'Recent'

    "Created: / 21-06-2011 / 08:35:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!BookmarkList class methodsFor:'class initialization'!

initializeBrowserBookmarks

    | file  |
    file := Filename defaultDirectory / 'browser-bookmarks.rc'.
    BrowserBookmarks := self readFromFile: file onError:[nil].
    BrowserBookmarks ifNotNil:[^self].    

    file := Filename homeDirectory / '.smalltalk' / 'browser-bookmarks.rc'.
    BrowserBookmarks := self readFromFile: file onError:[nil].
    BrowserBookmarks ifNotNil:[^self].    

    BrowserBookmarks := self new fileName: file pathName.

    "Created: / 23-05-2011 / 10:06:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 23-05-2011 / 16:35:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

initializeWebBookmarks

    | file  |
    file := Filename defaultDirectory / 'web-bookmarks.rc'.
    WebBookmarks := self readFromFile: file onError:[nil].
    WebBookmarks ifNotNil:[^self].    

    file := Filename homeDirectory / '.smalltalk' / 'web-bookmarks.rc'.
    WebBookmarks := self readFromFile: file onError:[nil].
    WebBookmarks ifNotNil:[^self].    

    WebBookmarks := self new fileName: file pathName.

    "Created: / 08-06-2011 / 12:15:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

initializeWorkspaceBookmarks

    | file  |
    file := Filename defaultDirectory / 'workspace-bookmarks.rc'.
    WorkspaceBookmarks := self readFromFile: file onError:[nil].
    WorkspaceBookmarks ifNotNil:[^self].    

    file := Filename homeDirectory / '.smalltalk' / 'workspace-bookmarks.rc'.
    WorkspaceBookmarks := self readFromFile: file onError:[nil].
    WorkspaceBookmarks ifNotNil:[^self].    

    WorkspaceBookmarks := self new fileName: file pathName.
    WorkspaceBookmarks root add: 
            ((Bookmark forFolderNamed: self defaultLabelForMyWorkspaces)
                add: (Bookmark forFile: WorkspaceApplication defaultMyWorkspaceDotWspFile pathName);
                yourself).

    "
        WorkspaceBookmarks := nil.
        BookmarkList initializeWorkspaceBookmarks.
    "

    "
        WorkspaceBookmarks := nil.
    "

    "Created: / 20-06-2011 / 22:10:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 21-06-2011 / 08:46:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!BookmarkList methodsFor:'accessing'!

/ label

    ^ self root / label

    "Created: / 21-06-2011 / 08:49:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

fileName
    ^ fileName
!

fileName:aString
    fileName := aString.
! !

!BookmarkList methodsFor:'accessing - special folders'!

myWorkspaces

    ^self / self class defaultLabelForMyWorkspaces

    "
        BookmarkList forWorkspace myWorkspaces      
    "

    "Created: / 21-06-2011 / 08:53:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!BookmarkList methodsFor:'change & update'!

changed:aParameter with:anArgument

    super changed:aParameter with:anArgument.
    "/self save.

    "Created: / 23-05-2011 / 16:13:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 02-06-2011 / 13:35:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!BookmarkList methodsFor:'collection protocol'!

add: item 

    ^root add: item

    "Created: / 23-05-2011 / 10:49:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 23-05-2011 / 13:45:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

contains: anObject

    ^root contains: anObject

    "Created: / 23-05-2011 / 10:44:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 23-05-2011 / 13:46:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

remove: item ifAbsent: block

    ^root remove: item

    "Created: / 23-05-2011 / 10:47:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 23-05-2011 / 13:48:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!BookmarkList methodsFor:'converting'!

asMenu

    ^root asMenu

    "Created: / 23-05-2011 / 10:31:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

asMenuUsingBuilder: builderClass

    ^self root asMenuUsingBuilder: builderClass

    "Created: / 21-06-2011 / 08:05:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

literalArrayEncoding

    ^Array 
        with: self className
        with: #root:
        with: root literalArrayEncoding

    "Created: / 23-05-2011 / 14:23:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!BookmarkList methodsFor:'initialization'!

initialize
    "Invoked when a new instance is created."

    "/ please change as required (and remove this comment)
    super initialize.

    showRoot := false.
    self root: (Bookmark forFolderNamed: '<bookmarks>').

    "Modified: / 23-05-2011 / 13:56:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!BookmarkList methodsFor:'loading / saving'!

save

    | f |

    (fileName notNil and:
        [(f := fileName asFilename) exists not or:
            [f isWritable]]) 
                ifTrue:[self saveOn: fileName].

    "Created: / 23-05-2011 / 16:38:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

saveOn: aStringOrFilename

    aStringOrFilename asFilename writingFileDo:
        [:s|s nextPutAll: self literalArrayEncoding storeString].

    "Created: / 23-05-2011 / 16:39:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!BookmarkList methodsFor:'visiting'!

acceptVisitor:aVisitor 
    "Double dispatch back to the visitor, passing my type encoded in
     the selector (visitor pattern)"

    "stub code automatically generated - please change if required"

    ^ aVisitor visitBookmarkList:self
! !

!BookmarkList class methodsFor:'documentation'!

version_CVS
    ^ '$Header: /cvs/stx/stx/libtool/BookmarkList.st,v 1.1 2011-07-01 13:15:35 cg Exp $'
!

version_SVN
    ^ '§Id§'
! !