StringPattern.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 09 Aug 2011 14:56:35 +0200
changeset 2619 0012c9536b98
child 2672 06e4ab62a588
permissions -rw-r--r--
initial checkin

"{ Package: 'stx:libbasic2' }"

Object subclass:#StringPattern
	instanceVariableNames:'data'
	classVariableNames:''
	poolDictionaries:''
	category:'Collections-Text-Support'
!

Object subclass:#Parser
	instanceVariableNames:'stream errorBlock'
	classVariableNames:''
	poolDictionaries:''
	privateIn:StringPattern
!

StringPattern subclass:#StartsWith
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:StringPattern
!

!StringPattern class methodsFor:'documentation'!

documentation
"
    A StringPattern instances are used to match string. The
    pattern is build from a user-supplied string. It is the
    intention to let the use type the search pattern - it can
    ve used for various live searches in lists, dialogs etc.

    This is an unfinished class. More detailed description about
    syntax and algorithm will be added once the results will be
    considered good and the API become stable. If not, blame on
    JV :-)

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

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!StringPattern class methodsFor:'instance creation'!

readFrom:aStringOrStream onError:exceptionBlock

    ^Parser parse: aStringOrStream readStream onError: exceptionBlock

    "Created: / 09-08-2011 / 13:39:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

startsWith: aString

    ^StartsWith new on: aString

    "Created: / 09-08-2011 / 13:42:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!StringPattern methodsFor:'initialization'!

on: anObject

    data := anObject.

    "Created: / 09-08-2011 / 13:42:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!StringPattern methodsFor:'matching'!

match: string 

    "Answers true if myself match the given string.
     No relaxing done"

    ^self match: string relax: 1.

    "Created: / 09-08-2011 / 13:51:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

match: string relax: relax

    "Answers true if myself match the given string.
     relax argument say how much the matching should
     be relaxed - relax is a number in <1..3>, where
     1 means no relaxing at all (aka exact match). 
     All patterns should support relax == 1. If the relax
     level is not supported by a pattern, false must be 
     returned."

    ^self subclassResponsibility

    "Created: / 09-08-2011 / 13:47:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!StringPattern::Parser class methodsFor:'parsing'!

parse: aStream onError: errorBlock

    ^self new parse: aStream onError: errorBlock

    "Created: / 09-08-2011 / 13:39:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!StringPattern::Parser methodsFor:'parsing'!

parse

    "Sorry, no fancy patterns now"

    ^StringPattern startsWith: stream contents.

    "Created: / 09-08-2011 / 13:41:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parse: aStream onError: aBlock

    stream := aStream.
    errorBlock := aBlock.
    ^self parse.

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

!StringPattern::StartsWith methodsFor:'matching'!

match: string relax: relax

    relax == 1 ifTrue:[
        ^string startsWith: data.
    ].
    relax == 2 ifTrue:[
        ^((string copyTo: data size) levenshteinTo: data) < 8"Wild guess, we will see"
    ].
    relax == 3 ifTrue:[
        ^((string copyTo: data size) levenshteinTo: data) < 14"Wild guess, we will see"
    ].
    ^false.

    "
        (StringPattern startsWith: 'String') match: 'StringPattern'
        (StringPattern startsWith: 'STring') match: 'StringPattern' relax: 2
    "

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

!StringPattern class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/StringPattern.st,v 1.1 2011-08-09 12:56:35 vrany Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libbasic2/StringPattern.st,v 1.1 2011-08-09 12:56:35 vrany Exp $'
! !