xquery/trunk/XQuery__FnLibrary.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 08 Apr 2008 19:47:42 +0000
changeset 0 5057afe1ec87
child 15 2e4ef5517c5e
permissions -rw-r--r--
Initial import from CVS

"{ Package: 'stx:goodies/xmlsuite/xquery' }"

"{ NameSpace: XQuery }"

FunctionLibrary subclass:#FnLibrary
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'XQuery-Libraries'
!


!FnLibrary methodsFor:'fn:*'!

absInContext: context withParameters: parameters forInterpreter: interpreter
   "
Summary: Returns the absolute value of $arg. If $arg is negative returns -$arg otherwise returns $arg.
If the argument is the empty sequence, the empty sequence is returned.
"

    self assert: parameters size = 1.

    parameters size = 0 ifTrue:[^XQuerySequence new:0].

    self assert: parameters size = 1.
    "/self assert: parameters first first type = XQuerySequenceItem typeNumber.

    ^XQuerySequence withNumber:(parameters first first value) abs.

    "Created: / 28-08-2007 / 23:46:52 / janfrog"
    "Modified: / 05-12-2007 / 15:56:42 / janfrog"
!

avgInContext: context withParameters: parameters forInterpreter: interpreter
"
     Summary: Returns the average of the values in the input sequence $arg, that is,
     the sum of the values divided by the number of values.

     If $arg is the empty sequence, the empty sequence is returned.

     If $arg contains values of type xs:untypedAtomic they are cast to xs:double.

     Duration values must either all be xs:yearMonthDuration values or must all be xs:dayTimeDuration values.
     For numeric values, the numeric promotion rules defined in 6.2 Operators on Numeric Values are used
     to promote all values to a single common type.
     After these operations, $arg must contain items of a single type,
     which must be one of the four numeric types, xs:yearMonthDuration or xs:dayTimeDuration or one if its subtypes.

     If the above conditions are not met, then a type error is raised [err:FORG0006]."

    |sumContext countContext|

    self assert:parameters size = 1.
    parameters first dataContext size = 0 ifTrue:[
        ^ XQueryContext new dataContextEmpty.
    ].
    sumContext := self 
                    sumInContext: context
                    withParameters: parameters
                    forInterpreter: interpreter.
    countContext := self 
                    countInContext: context
                    withParameters: parameters
                    forInterpreter: interpreter.
    ^ XQueryContext 
        withSingleNumber:(sumContext dataContext first value 
                / countContext dataContext first value) asDouble.

    "Created: / 29-08-2007 / 07:42:02 / janfrog"
!

booleanInContext: context withParameters: parameters forInterpreter: interpreter
    "
       Summary: Computes the effective boolean value of the sequence $arg.

      If $arg is the empty sequence, fn:boolean returns false.

      If $arg is a sequence whose first item is a node, fn:boolean returns true.

      If $arg is a singleton value of type xs:boolean or a derived from xs:boolean, fn:boolean returns $arg.

      If $arg is a singleton value of type xs:string or a type derived from xs:string,
      xs:anyURI or a type derived from xs:anyURI or xs:untypedAtomic, fn:boolean returns false
      if the operand value has zero length; otherwise it returns true.

      If $arg is a singleton value of any numeric type or a type derived from a numeric type,
      fn:boolean returns false if the operand value is NaN or is numerically equal to zero; otherwise it returns true.

      In all other cases, fn:boolean raises a type error [err:FORG0006].
"
    self assert: parameters size = 1.

    ^XQuerySequence withBoolean: parameters first effectiveBooleanValue

    "Created: / 28-08-2007 / 23:45:06 / janfrog"
!

ceilingInContext: context withParameters: parameters forInterpreter: interpreter
"
Summary: Returns the smallest (closest to negative infinity) number with no fractional part
that is not less than the value of $arg.
If the argument is the empty sequence, the empty sequence is returned.
"

    self assert: parameters size = 1.

    parameters first dataContext size = 0 ifTrue:[
        ^XQueryContext new
                    dataContextEmpty.
    ].

    self assert: parameters first dataContext size = 1.
    "/self assert: parameters first dataContext first type = XQuerySequenceItem typeNumber.

    ^XQueryContext withSingleNumber: (parameters first dataContext first value) ceiling.

    "Created: / 29-08-2007 / 08:12:37 / janfrog"
    "Modified: / 05-12-2007 / 21:00:02 / janfrog"
!

collectionInContext: context withParameters: parameters forInterpreter: interpreter

    | uriString documentAdaptors |

    self assert: parameters size <= 1 message:'Zero or one argument expected'.
    uriString := parameters size = 1 
                    ifTrue:[parameters first first value asString]
                    ifFalse:[nil].

    documentAdaptors := (interpreter xqueryExecutor documentAdaptorsFor:uriString).

    ^XQuerySequence withAll:
        (documentAdaptors collect:
            [:documentAdaptor|
                XQuerySequenceItem with:
                    (XQueryAccessedNode new 
                        documentAdaptor: documentAdaptor;
                            nodeId: documentAdaptor xpathDocument)])

    "Created: / 20-09-2007 / 10:53:03 / janfrog"
    "Modified: / 20-09-2007 / 12:16:28 / janfrog"
!

concatInContext:context withParameters:parameters forInterpreter:interpreter 

    | stringStream |
    stringStream := UnicodeString new writeStream.
    parameters do:
        [:paramSeq|
        paramSeq do:
            [:seqItem|
            stringStream nextPutAll: seqItem stringValue]].

    ^ XQuerySequence 
        withString:stringStream contents

    "Created: / 19-11-2007 / 14:21:46 / janfrog"
!

countInContext: context withParameters: parameters forInterpreter: interpreter
 "
Summary: Returns the number of items in the value of $arg.

Returns 0 if $arg is the empty sequence.
"
    self assert: parameters size = 1.

     ^XQuerySequence withNumber: parameters first size.

    "Created: / 28-08-2007 / 23:47:31 / janfrog"
!

distinctValuesInContext:context withParameters:parameters forInterpreter:interpreter 
    "
   Summary: Returns the sequence that results from removing from $arg all but one of a set of values that are eq to one other.
   Values of type xs:untypedAtomic are compared as if they were of type xs:string. Values that cannot be compared,
   i.e. the eq operator is not defined for their types, are considered to be distinct.
   The order in which the sequence of values is returned is implementation dependent.

   If $arg is the empty sequence, the empty sequence is returned."
    
    |sequence sequenceValues result|

    self assert:(parameters size = 1).
    result := XQuerySequence new.
    sequence := parameters first.
    sequenceValues := Set new.
    sequence do:
        [:seqItem|
        |seqItemValue|
        seqItemValue := seqItem value.
        (sequenceValues includes:seqItemValue)
            ifFalse:
                [result add: seqItem.
                sequenceValues add: seqItemValue]].
    ^result

    "
    parameters first dataContext size = 0 ifTrue:[
        ^ XQueryContext new dataContextEmpty.
    ].
    valuesCollection := OrderedCollection new.
    resultDataContext := OrderedCollection new.
    parameters first dataContext do:[:dataContextItem | 
        itemValue := dataContextItem value.
        (valuesCollection anySatisfy:[:value | itemValue = value ]) ifFalse:[
            valuesCollection add:itemValue.
            resultDataContext add:dataContextItem.
        ].
    ].
     "

    "Created: / 29-08-2007 / 08:45:39 / janfrog"
    "Modified: / 20-09-2007 / 15:47:34 / janfrog"
!

docInContext: context withParameters: parameters forInterpreter: interpreter

    "
    Summary: Retrieves a document using an xs:anyURI, which may include a fragment identifier, supplied as an xs:string.
    If $uri is not a valid xs:anyURI, an error is raised [err:FODC0005].
    If it is a relative URI Reference, it is resolved relative to the value of the base URI property from the static context.
    The resulting absolute URI Reference is promoted to an xs:string.
    If the Available documents discussed in Section 2.1.2 Dynamic ContextXP provides a mapping from this string
    to a document node, the function returns that document node. If the Available documents provides no mapping for the string,
    an error is raised [err:FODC0005].

    If $uri is the empty sequence, the result is an empty sequence.
"
    | uriString documentAdaptors |

    self assert: parameters size = 1 message:'Exactly one argument expected'.
    uriString := parameters first first value asString.
    documentAdaptors := (interpreter xqueryExecutor documentAdaptorsFor:uriString).
    self assert: documentAdaptors size = 1 message:'No or more documents matches given URI. Use fn:collection() instead'.

    ^XQuerySequence withNode:
                (XQueryAccessedNode new 
                    documentAdaptor: documentAdaptors first;
                        nodeId: documentAdaptors first xpathDocument)

    "Created: / 28-08-2007 / 23:41:08 / janfrog"
    "Modified: / 20-09-2007 / 10:30:15 / janfrog"
!

documentUriInContext: context withParameters: parameters forInterpreter: interpreter

    | node |
    parameters size = 0 ifTrue:[^XQuerySequence new].
    node := parameters first first item.
    ^node isDocumentNode 
            ifTrue:
                [XQuerySequence withString:node documentURI asString]
            ifFalse:
                [XQuerySequence new]

    "Created: / 20-09-2007 / 14:43:23 / janfrog"
!

emptyInContext:context withParameters:parameters forInterpreter:interpreter 
    "
     Summary: If the value of $arg is the empty sequence, the function returns true; otherwise, the function returns false."
    
    self assert:parameters size = 1.
    ^ XQueryContext withSingleBoolean:parameters first dataContext size = 0.

    "Created: / 29-08-2007 / 09:09:33 / janfrog"
!

exactlyOneInContext:context withParameters:parameters forInterpreter:interpreter 
    "
     Summary: Returns $arg if it contains exactly one item. Otherwise, raises an error [err:FORG0005]."
    
    self assert:parameters size = 1.
    self assert:parameters first dataContext size = 1.
    ^ parameters first.

    "Created: / 29-08-2007 / 09:10:01 / janfrog"
!

existsInContext:context withParameters:parameters forInterpreter:interpreter 
    "
     Summary: If the value of $arg is not the empty sequence, the function returns true; otherwise, the function returns false."
    
    self assert:parameters size = 1.
    ^ XQueryContext withSingleBoolean:parameters first dataContext size > 0.

    "Created: / 29-08-2007 / 09:10:43 / janfrog"
!

falseInContext:context withParameters:parameters forInterpreter:interpreter 
    "
     Summary: Returns the xs:boolean value false. Equivalent to xs:boolean('0')."
    
    self assert:parameters size = 0.
    ^ XQueryContext withSingleBoolean:false.

    "Created: / 29-08-2007 / 09:10:49 / janfrog"
!

floorInContext:context withParameters:parameters forInterpreter:interpreter 
    "
     Summary: Returns the largest (closest to positive infinity) number with no fractional part
     that is not greater than the value of $arg.
     If the argument is the empty sequence, the empty sequence is returned."
    
    self assert:parameters size = 1.
    parameters first dataContext size = 0 ifTrue:[
        ^ XQueryContext new dataContextEmpty.
    ].
    self assert:parameters first dataContext size = 1.
    "/self assert:parameters first dataContext first type 
    "/            = XQuerySequenceItem typeNumber.
    ^ XQueryContext 
        withSingleNumber:(parameters first dataContext first value) floor.

    "Created: / 29-08-2007 / 09:10:55 / janfrog"
    "Modified: / 05-12-2007 / 21:00:10 / janfrog"
!

insertBeforeInContext:context withParameters:parameters forInterpreter:interpreter 
    "
     Summary: Returns a new sequence constructed from the value of $target with the value of $inserts
     inserted at the position specified by the value of $position.
     (The value of $target is not affected by the sequence construction.)

     If $target is the empty sequence, $inserts is returned. If $inserts is the empty sequence, $target is returned.

     The value returned by the function consists of all items of $target whose index is less than $position,
     followed by all items of $inserts, followed by the remaining elements of $target, in that sequence.

     If $position is less than one (1), the first position, the effective value of $position is one (1).
     If $position is greater than the number of items in $target, then the effective value of $position
     is equal to the number of items in $target plus 1."
    
    |index resultDataContext|

    self assert:parameters size = 3.
    parameters first dataContext size = 0 ifTrue:[
        ^ parameters third.
    ].
    parameters third dataContext size = 0 ifTrue:[
        ^ parameters first.
    ].
    self assert:parameters second dataContext size = 1.
    "/self assert:parameters second dataContext first type 
    "/            = XQuerySequenceItem typeNumber.
    index := parameters second dataContext first value.
    index < 1 ifTrue:[
        index := 1.
    ].
    index > parameters first dataContext size ifTrue:[
        index := parameters first dataContext size + 1.
    ].
    resultDataContext := OrderedCollection new 
                addAll:parameters first dataContext.
    resultDataContext addAll:parameters third dataContext beforeIndex:index.
    ^ XQueryContext new dataContext:resultDataContext.

    "Created: / 29-08-2007 / 09:11:05 / janfrog"
    "Modified: / 05-12-2007 / 21:00:17 / janfrog"
!

lastInContext:context withParameters:parameters forInterpreter:interpreter 
    "
     Summary: Returns the context size from the dynamic context.
     If the context item is undefined, an error is raised: [err:XPDY0002]."
    
    self assert:parameters size = 0.
    self assert:(self givenContext optContext at:#innerFocus) isNil not.
    ^ XQueryContext 
        withSingleNumber:(self givenContext optContext at:#innerFocus) contextSize.

    "Created: / 29-08-2007 / 09:11:12 / janfrog"
!

localNameInContext:context withParameters:parameters forInterpreter:interpreter 

    self assert:parameters size = 1.
    self assert:parameters first size = 1.
    self assert:parameters first first containsNode.
    self assert:parameters first first item isElementOrAttributeNode.
    ^ XQuerySequence 
        withString:(parameters first first item xpathLocalName)

    "Created: / 19-11-2007 / 14:10:25 / janfrog"
!

maxInContext:context withParameters:parameters forInterpreter:interpreter 
    "
     Summary: Selects an item from the input sequence $arg whose value is greater than or equal to the value of every other item
     in the input sequence. If there are two or more such items, then the specific item whose value is returned
     is implementation dependent."
    
    |chosenItem|

    self assert:parameters size = 1.
    parameters first dataContext size = 0 ifTrue:[
        ^ XQueryContext new dataContextEmpty.
    ].
    parameters first dataContext do:[:dataContextItem | 
        chosenItem 
            ifNil:[ chosenItem := dataContextItem. ]
            ifNotNil:[
                chosenItem value < dataContextItem value ifTrue:[
                    chosenItem := dataContextItem.
                ].
            ].
    ].
    ^ XQueryContext new dataContextSingle:chosenItem.

    "Created: / 29-08-2007 / 09:11:19 / janfrog"
!

minInContext:context withParameters:parameters forInterpreter:interpreter 
    "
     Summary: Selects an item from the input sequence $arg whose value is greater than or equal to the value of every other item
     in the input sequence. If there are two or more such items, then the specific item whose value is returned
     is implementation dependent."
    
    |chosenItem|

    self assert:parameters size = 1.
    parameters first dataContext size = 0 ifTrue:[
        ^ XQueryContext new dataContextEmpty.
    ].
    parameters first dataContext do:[:dataContextItem | 
        chosenItem 
            ifNil:[ chosenItem := dataContextItem. ]
            ifNotNil:[
                chosenItem value < dataContextItem value ifTrue:[
                    chosenItem := dataContextItem.
                ].
            ].
    ].
    ^ XQueryContext new dataContextSingle:chosenItem.

    "Created: / 29-08-2007 / 09:11:39 / janfrog"
!

notInContext:context withParameters:parameters forInterpreter:interpreter 
    "
     Summary: $arg is first reduced to an effective boolean value by applying the fn:boolean() function.
     Returns true if the effective boolean value is false, and false if the effective boolean value is true."
    
    self assert:parameters size = 1.
    ^ XQueryContext 
        withSingleBoolean:((XQueryFnBoolean new)
                setContext:self givenContext;
                setParameters:parameters;
                setXQueryInterpreter:self xqueryInterpreter;
                evaluate) dataContext 
                first value 
                not.

    "Created: / 29-08-2007 / 09:12:12 / janfrog"
!

oneOrMoreInContext:context withParameters:parameters forInterpreter:interpreter 
    "
     Summary: Returns $arg if it contains one or more items. Otherwise, raises an error [err:FORG0004]."
    
    self assert:parameters size = 1.
    self assert:parameters first dataContext size > 0.
    ^ parameters first.

    "Created: / 29-08-2007 / 09:12:25 / janfrog"
!

positionInContext:context withParameters:parameters forInterpreter:interpreter 
    "
     Summary: Returns the context position from the dynamic context.
     If the context item is undefined, an error is raised: [err:XPDY0002]."
    
    self assert:parameters size = 0.
    self assert:(self givenContext optContext at:#innerFocus) isNil not.
    ^ XQueryContext 
        withSingleNumber:(self givenContext optContext at:#innerFocus) 
                contextPosition.

    "Modified: / 24-11-2006 / 11:40:47 / ked"
    "Created: / 29-08-2007 / 09:12:38 / janfrog"
!

putInContext:context withParameters:parameters forInterpreter:interpreter 
    "fn:put($node as node(), $uri as xs:string) as empty-sequence()
     Summary: Stores a document or element to the location specified by $uri.
     This function is normally invoked to create a resource on an external
     storage system such as a file system or a database."

    | documentURI |

    self 
        assert:parameters size = 2 message: 'Two parameters required, ', parameters size printString , ' given';
        assert:parameters first containsSingleElementOrDocument message:'First parameter must be signleton sequence with document od element node';
        assert:parameters second containsSingleString message:'Second parameter must be signleton sequence with xs:string'.


    documentURI := parameters second first value asURI.

    self
        assert: (documentURI isKindOf: FileURI) message:'For now, only file:// URIs are supported'.

    documentURI writeStreamDo:
        [:writeStream :attributes|
        writeStream nextPutAll: (XQueryResult withAll: parameters first) asDocumentWithoutComment asXMLString].

    ^ XQuerySequence new.
!

removeInContext:context withParameters:parameters forInterpreter:interpreter 
    "
     Summary: Returns a new sequence constructed from the value of $target with the item at the position
     specified by the value of $position removed.

     If $position is less than 1 or greater than the number of items in $target, $target is returned.
     Otherwise, the value returned by the function consists of all items of $target whose index is less than $position,
     followed by all items of $target whose index is greater than $position.
     If $target is the empty sequence, the empty sequence is returned."
    
    |index resultDataContext|

    self assert:parameters size = 2.
    parameters first dataContext size = 0 ifTrue:[
        ^ XQueryContext new dataContextEmpty.
    ].
    self assert:parameters second dataContext size = 1.
    "/self assert:parameters second dataContext first type 
    "/            = XQuerySequenceItem typeNumber.
    index := parameters second dataContext first value.
    index < 1 ifTrue:[
        ^ parameters first.
    ].
    index > parameters first dataContext size ifTrue:[
        ^ parameters first.
    ].
    resultDataContext := OrderedCollection new 
                addAll:parameters first dataContext.
    resultDataContext removeFromIndex:index toIndex:index.
    ^ XQueryContext new dataContext:resultDataContext.

    "Created: / 29-08-2007 / 09:12:44 / janfrog"
    "Modified: / 05-12-2007 / 21:00:24 / janfrog"
!

reverseInContext:context withParameters:parameters forInterpreter:interpreter 
    "
     Summary: Reverses the order of items in a sequence. If $arg is the empty sequence, the empty sequence is returned."
    
    |resultDataContext|

    self assert:parameters size = 1.
    parameters first dataContext size = 0 ifTrue:[
        ^ XQueryContext new dataContextEmpty.
    ].
    resultDataContext := OrderedCollection new 
                addAll:parameters first dataContext.
    resultDataContext reverse.
    ^ XQueryContext new dataContext:resultDataContext.

    "Created: / 29-08-2007 / 09:13:02 / janfrog"
!

rootInContext: context withParameters: parameters forInterpreter: interpreter

    | node |
    parameters size = 0 ifTrue:[^XQuerySequence new].
    node := parameters first first item.
    ^XQuerySequence with:(node xpathAncestor last)

    "Created: / 20-09-2007 / 15:14:06 / janfrog"
!

roundInContext:context withParameters:parameters forInterpreter:interpreter 
    "
     Summary: Returns the number with no fractional part that is closest to the argument. If there are two such numbers,
     then the one that is closest to positive infinity is returned.
     If the argument is the empty sequence, the empty sequence is returned."
    
    self assert:parameters size = 1.
    parameters first dataContext size = 0 ifTrue:[
        ^ XQueryContext new dataContextEmpty.
    ].
    self assert:parameters first dataContext size = 1.
    "/self assert:parameters first dataContext first type 
    "/            = XQuerySequenceItem typeNumber.
    ^ XQueryContext 
        withSingleNumber:((parameters first dataContext first value) > 0 
                ifTrue:[ (parameters first dataContext first value) rounded. ]
                ifFalse:[ (parameters first dataContext first value) truncated. ]).

    "Created: / 29-08-2007 / 09:13:10 / janfrog"
    "Modified: / 05-12-2007 / 21:00:30 / janfrog"
!

subsequenceInContext:context withParameters:parameters forInterpreter:interpreter 
    "
     Summary: Returns the contiguous sequence of items in the value of $sourceSeq beginning at the position
     indicated by the value of $startingLoc and continuing for the number of items indicated by the value of $length.

     If $sourceSeq is the empty sequence, the empty sequence is returned.

     If $startingLoc is zero or negative, the subsequence includes items from the beginning of the $sourceSeq.

     If $length is not specified, the subsequence includes items to the end of $sourceSeq.

     If $length is greater than the number of items in the value of $sourceSeq following $startingLoc, the subsequence includes items to the end of $sourceSeq.

     The first item of a sequence is located at position 1, not position 0."
    
    |start stop resultDataContext|

    self assert:(parameters size = 2 or:[ parameters size = 3 ]).
    parameters first dataContext size = 0 ifTrue:[
        ^ XQueryContext new dataContextEmpty.
    ].
    self assert:parameters second dataContext size = 1.
    "/self assert:parameters second dataContext first type 
    "/            = XQuerySequenceItem typeNumber.
    start := parameters second dataContext first value.
    start < 1 ifTrue:[
        start := 1.
    ].
    parameters size = 3 ifTrue:[
        self assert:parameters third dataContext size = 1.
        "/self assert:parameters third dataContext first type 
        "/            = XQuerySequenceItem typeNumber.
        stop := parameters third dataContext first value + start - 1.
        stop > parameters first dataContext size ifTrue:[
            stop := parameters first dataContext size.
        ].
    ] ifFalse:[
        stop := parameters first dataContext size.
    ].
    resultDataContext := parameters first dataContext copyFrom:start to:stop.
    ^ XQueryContext new dataContext:resultDataContext.

    "Created: / 29-08-2007 / 09:07:19 / janfrog"
    "Modified: / 05-12-2007 / 21:00:44 / janfrog"
!

sumInContext: context withParameters: parameters forInterpreter: interpreter
   "
Summary: Returns a value obtained by adding together the values in $arg.
If $zero is not specified, then the value returned for an empty sequence is the xs:integer value 0.
If $zero is specified, then the value returned for an empty sequence is $zero.

Any values of type xs:untypedAtomic in $arg are cast to xs:double.
The items in the resulting sequence may be reordered in an arbitrary order.
The resulting sequence is referred to below as the converted sequence.

If the converted sequence is empty, then the single-argument form of the function returns the xs:integer value 0;
the two-argument form returns the value of the argument $zero
"

    | sumAccum |

    self assert: (parameters size = 1 
        or:[parameters size = 2]).

    parameters first size = 0 ifTrue:[
        parameters size = 2 ifTrue:[
            ^parameters second.
        ] ifFalse:[
            ^XQueryContext withSingleNumber: 0.
        ].
    ].

    sumAccum := 0.

    parameters first do:[:dataContextItem |
        sumAccum := sumAccum + dataContextItem value.
    ].

    ^XQuerySequence withNumber: sumAccum.

    "Created: / 28-08-2007 / 23:43:21 / janfrog"
    "Modified: / 05-12-2007 / 15:42:27 / janfrog"
!

trueInContext:context withParameters:parameters forInterpreter:interpreter 
    "
     Summary: Returns the xs:boolean value true. Equivalent to xs:boolean('1')."
    
    self assert:parameters size = 0.
    ^ XQueryContext withSingleBoolean:true.

    "Created: / 29-08-2007 / 09:08:19 / janfrog"
!

zeroOrOneInContext:context withParameters:parameters forInterpreter:interpreter 
    "
     Summary: Returns $arg if it contains zero or one items. Otherwise, raises an error [err:FORG0003]."
    
    self assert:parameters size = 1.
    self assert:parameters first dataContext size < 2.
    ^ parameters first.

    "Created: / 29-08-2007 / 09:09:01 / janfrog"
! !

!FnLibrary methodsFor:'function library API'!

defaultPrefix
    "Superclass says that I am responsible to implement this method"

    ^'fn'

    "Created: / 29-08-2007 / 09:37:40 / janfrog"
!

functionLocalNames

    ^#(
        abs
        avg
        boolean
        ceiling
        count
        collection
        concat
        #'distinct-values'
        doc
        #'document-uri'
        empty
        #'exactly-one'
        exists
        false
        floor
        #'insert-before'
        last
        #'local-name'
        max
        min
        not
        #'one-or-more'
        position
        put
        remove
        reverse
        root
        round
        subsequence
        sum
        true
        #'zero-or-one'
    )

    "Created: / 28-08-2007 / 23:12:35 / janfrog"
    "Modified: / 19-11-2007 / 14:18:06 / janfrog"
!

namespaceURI

    ^'http://www.w3.org/2005/xpath-functions'

    "Created: / 28-08-2007 / 23:03:37 / janfrog"
! !

!FnLibrary class methodsFor:'documentation'!

version
    ^ '$Header: /opt/data/cvs/stx/goodies/xmlsuite/xquery/XQuery__FnLibrary.st,v 1.7 2008-01-09 14:08:02 wrobll1 Exp $'
! !