]> git.donarmstrong.com Git - lilypond.git/blob - scm/lily-library.scm
Merge branch 'master' into translation
[lilypond.git] / scm / lily-library.scm
1 ;;;; This file is part of LilyPond, the GNU music typesetter.
2 ;;;;
3 ;;;; Copyright (C) 1998--2015 Jan Nieuwenhuizen <janneke@gnu.org>
4 ;;;; Han-Wen Nienhuys <hanwen@xs4all.nl>
5 ;;;;
6 ;;;; LilyPond is free software: you can redistribute it and/or modify
7 ;;;; it under the terms of the GNU General Public License as published by
8 ;;;; the Free Software Foundation, either version 3 of the License, or
9 ;;;; (at your option) any later version.
10 ;;;;
11 ;;;; LilyPond is distributed in the hope that it will be useful,
12 ;;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
13 ;;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14 ;;;; GNU General Public License for more details.
15 ;;;;
16 ;;;; You should have received a copy of the GNU General Public License
17 ;;;; along with LilyPond.  If not, see <http://www.gnu.org/licenses/>.
18
19 ;; for take, drop, take-while, list-index, and find-tail:
20 (use-modules (srfi srfi-1))
21
22 ;; for define-safe-public when byte-compiling using Guile V2
23 (use-modules (scm safe-utility-defs))
24
25 (use-modules (ice-9 pretty-print))
26
27 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
28 ;; constants.
29
30 (define-public X 0)
31 (define-public Y 1)
32 (define-safe-public START -1)
33 (define-safe-public STOP 1)
34 (define-public LEFT -1)
35 (define-public RIGHT 1)
36 (define-public UP 1)
37 (define-public DOWN -1)
38 (define-public CENTER 0)
39
40 (define-safe-public DOUBLE-FLAT  -1)
41 (define-safe-public THREE-Q-FLAT -3/4)
42 (define-safe-public FLAT -1/2)
43 (define-safe-public SEMI-FLAT -1/4)
44 (define-safe-public NATURAL 0)
45 (define-safe-public SEMI-SHARP 1/4)
46 (define-safe-public SHARP 1/2)
47 (define-safe-public THREE-Q-SHARP 3/4)
48 (define-safe-public DOUBLE-SHARP 1)
49 (define-safe-public SEMI-TONE 1/2)
50
51 (define-safe-public INFINITY-INT 1000000)
52
53 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
54 ;; moments
55
56 (define-public ZERO-MOMENT (ly:make-moment 0 1))
57
58 (define-public (moment-min a b)
59   (if (ly:moment<? a b) a b))
60
61 (define-public (moment<=? a b)
62   (or (equal? a b)
63       (ly:moment<? a b)))
64
65 (define-public (fraction->moment fraction)
66   (if (null? fraction)
67       ZERO-MOMENT
68       (ly:make-moment (car fraction) (cdr fraction))))
69
70 (define-public (moment->fraction moment)
71   (cons (ly:moment-main-numerator moment)
72         (ly:moment-main-denominator moment)))
73
74 (define-public (seconds->moment s context)
75   "Return a moment equivalent to s seconds at the current tempo."
76   (ly:moment-mul (ly:context-property context 'tempoWholesPerMinute)
77                  (ly:make-moment (/ s 60))))
78
79 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
80 ;; durations
81
82 (define-public (duration-log-factor lognum)
83   "Given a logarithmic duration number, return the length of the duration,
84 as a number of whole notes."
85   (or (and (exact? lognum) (integer? lognum))
86       (scm-error 'wrong-type-arg "duration-log-factor" "Not an integer: ~S" (list lognum) #f))
87   (if (<= lognum 0)
88       (ash 1 (- lognum))
89       (/ (ash 1 lognum))))
90
91 (define-public (duration-dot-factor dotcount)
92   "Given a count of the dots used to extend a musical duration, return
93 the numeric factor by which they increase the duration."
94   (or (and (exact? dotcount) (integer? dotcount) (>= dotcount 0))
95       (scm-error 'wrong-type-arg "duration-dot-factor" "Not a count: ~S" (list dotcount) #f))
96   (- 2 (/ (ash 1 dotcount))))
97
98 (define-public (duration-length dur)
99   "Return the overall length of a duration, as a number of whole
100 notes.  (Not to be confused with ly:duration-length, which returns a
101 less-useful moment object.)"
102   (ly:moment-main (ly:duration-length dur)))
103
104 (define-public (duration-visual dur)
105   "Given a duration object, return the visual part of the duration (base
106 note length and dot count), in the form of a duration object with
107 non-visual scale factor 1."
108   (ly:make-duration (ly:duration-log dur) (ly:duration-dot-count dur) 1))
109
110 (define-public (duration-visual-length dur)
111   "Given a duration object, return the length of the visual part of the
112 duration (base note length and dot count), as a number of whole notes."
113   (duration-length (duration-visual dur)))
114
115 (define-public (unity-if-multimeasure context dur)
116   "Given a context and a duration, return @code{1} if the duration is
117 longer than the @code{measureLength} in that context, and @code{#f} otherwise.
118 This supports historic use of @code{Completion_heads_engraver} to split
119 @code{c1*3} into three whole notes."
120   (if (ly:moment<? (ly:context-property context 'measureLength)
121                    (ly:duration-length dur))
122     1
123     #f))
124
125 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
126 ;; arithmetic
127 (define-public (average x . lst)
128   (/ (+ x (apply + lst)) (1+ (length lst))))
129
130 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
131 ;; parser <-> output hooks.
132
133 (define-public (collect-bookpart-for-book book-part)
134   "Toplevel book-part handler."
135   (define (add-bookpart book-part)
136     (ly:parser-define! 'toplevel-bookparts
137      (cons book-part (ly:parser-lookup 'toplevel-bookparts))))
138   ;; If toplevel scores have been found before this \bookpart,
139   ;; add them first to a dedicated bookpart
140   (if (pair? (ly:parser-lookup 'toplevel-scores))
141       (begin
142         (add-bookpart (ly:make-book-part
143                        (ly:parser-lookup 'toplevel-scores)))
144         (ly:parser-define! 'toplevel-scores (list))))
145   (add-bookpart book-part))
146
147 (define-public (collect-scores-for-book score)
148   (ly:parser-define! 'toplevel-scores
149    (cons score (ly:parser-lookup 'toplevel-scores))))
150
151 (define-public (collect-music-aux score-handler music)
152   (define (music-property symbol)
153     (ly:music-property music symbol #f))
154   (cond ((music-property 'page-marker)
155          ;; a page marker: set page break/turn permissions or label
156          (let ((label (music-property 'page-label)))
157            (if (symbol? label)
158                (score-handler (ly:make-page-label-marker label))))
159          (for-each (lambda (symbol)
160                      (let ((permission (music-property symbol)))
161                        (if (symbol? permission)
162                            (score-handler
163                             (ly:make-page-permission-marker symbol
164                                                             (if (eq? 'forbid permission)
165                                                                 '()
166                                                                 permission))))))
167                    '(line-break-permission page-break-permission
168                                            page-turn-permission)))
169         ((not (music-property 'void))
170          ;; a regular music expression: make a score with this music
171          ;; void music is discarded
172          (score-handler (scorify-music music)))))
173
174 (define-public (collect-music-for-book music)
175   "Top-level music handler."
176   (collect-music-aux (lambda (score)
177                        (collect-scores-for-book score))
178                      music))
179
180 (define-public (collect-book-music-for-book book music)
181   "Book music handler."
182   (collect-music-aux (lambda (score)
183                        (ly:book-add-score! book score))
184                      music))
185
186 (define-public (scorify-music music)
187   "Preprocess @var{music}."
188   (ly:make-score
189    (fold (lambda (f m) (f m))
190          music
191          toplevel-music-functions)))
192
193 (define (get-current-filename book)
194   "return any suffix value for output filename allowing for settings by
195 calls to bookOutputName function"
196   (or (paper-variable book 'output-filename)
197       (ly:parser-output-name)))
198
199 (define (get-current-suffix book)
200   "return any suffix value for output filename allowing for settings by calls to
201 bookoutput function"
202   (let ((book-output-suffix (paper-variable book 'output-suffix)))
203     (if (not (string? book-output-suffix))
204         (ly:parser-lookup 'output-suffix)
205         book-output-suffix)))
206
207 (define-public current-outfile-name #f)  ; for use by regression tests
208
209 (define (get-outfile-name book)
210   "return current filename for generating backend output files"
211   ;; user can now override the base file name, so we have to use
212   ;; the file-name concatenated with any potential output-suffix value
213   ;; as the key to out internal a-list
214   (let* ((base-name (get-current-filename book))
215          (output-suffix (get-current-suffix book))
216          (alist-key (format #f "~a~a" base-name output-suffix))
217          (counter-alist (ly:parser-lookup 'counter-alist))
218          (output-count (assoc-get alist-key counter-alist 0))
219          (result base-name))
220     ;; Allow all ASCII alphanumerics, including accents
221     (if (string? output-suffix)
222         (set! result
223               (format #f "~a-~a"
224                       result
225                       (string-regexp-substitute
226                        "[^-[:alnum:]]"
227                        "_"
228                        output-suffix))))
229
230     ;; assoc-get call will always have returned a number
231     (if (> output-count 0)
232         (set! result (format #f "~a-~a" result output-count)))
233
234     (ly:parser-define! 'counter-alist
235      (assoc-set! counter-alist alist-key (1+ output-count)))
236     (set! current-outfile-name result)
237     result))
238
239 (define (print-book-with book process-procedure)
240   (let* ((paper (ly:parser-lookup '$defaultpaper))
241          (layout (ly:parser-lookup '$defaultlayout))
242          (outfile-name (get-outfile-name book)))
243     (process-procedure book paper layout outfile-name)))
244
245 (define-public (print-book-with-defaults book)
246   (print-book-with book ly:book-process))
247
248 (define-public (print-book-with-defaults-as-systems book)
249   (print-book-with book ly:book-process-to-systems))
250
251 ;; Add a score to the current bookpart, book or toplevel
252 (define-public (add-score score)
253   (cond
254    ((ly:parser-lookup '$current-bookpart)
255     ((ly:parser-lookup 'bookpart-score-handler)
256      (ly:parser-lookup '$current-bookpart) score))
257    ((ly:parser-lookup '$current-book)
258     ((ly:parser-lookup 'book-score-handler)
259      (ly:parser-lookup '$current-book) score))
260    (else
261     ((ly:parser-lookup 'toplevel-score-handler) score))))
262
263 (define-public paper-variable
264   (let
265       ((get-papers
266         (lambda (book)
267           (append (if (and book (ly:output-def? (ly:book-paper book)))
268                       (list (ly:book-paper book))
269                       '())
270                   (ly:parser-lookup '$papers)
271                   (list (ly:parser-lookup '$defaultpaper))))))
272     (make-procedure-with-setter
273      (lambda (book symbol)
274        (any (lambda (p) (ly:output-def-lookup p symbol #f))
275             (get-papers book)))
276      (lambda (book symbol value)
277        (ly:output-def-set-variable!
278         (car (get-papers book))
279         symbol value)))))
280
281 (define-public (add-text text)
282   (add-score (list text)))
283
284 (define-public (add-music music)
285   (collect-music-aux (lambda (score)
286                        (add-score score))
287                      music))
288
289 (define-public (context-mod-from-music music)
290   (let ((warn #t) (mods (ly:make-context-mod)))
291     (let loop ((m music))
292       (if (music-is-of-type? m 'layout-instruction-event)
293           (let ((symbol (ly:music-property m 'symbol)))
294             (ly:add-context-mod
295              mods
296              (case (ly:music-property m 'name)
297                ((PropertySet)
298                 (list 'assign
299                       symbol
300                       (ly:music-property m 'value)))
301                ((PropertyUnset)
302                 (list 'unset symbol))
303                ((OverrideProperty)
304                 (cons* 'push
305                        symbol
306                        (ly:music-property m 'grob-value)
307                        (cond
308                         ((ly:music-property m 'grob-property #f) => list)
309                         (else
310                          (ly:music-property m 'grob-property-path)))))
311                ((RevertProperty)
312                 (cons* 'pop
313                        symbol
314                        (cond
315                         ((ly:music-property m 'grob-property #f) => list)
316                         (else
317                          (ly:music-property m 'grob-property-path))))))))
318           (case (ly:music-property m 'name)
319             ((ApplyContext)
320              (ly:add-context-mod mods
321                                  (list 'apply
322                                        (ly:music-property m 'procedure))))
323             ((ContextSpeccedMusic)
324              (loop (ly:music-property m 'element)))
325             (else
326              (let ((callback (ly:music-property m 'elements-callback)))
327                (if (procedure? callback)
328                    (for-each loop (callback m))
329                    (if (and warn (ly:duration? (ly:music-property m 'duration)))
330                        (begin
331                          (ly:music-warning
332                           music
333                           (_ "Music unsuitable for context-mod"))
334                          (set! warn #f)))))))))
335     mods))
336
337 (define-public (context-defs-from-music output-def music)
338   (let ((warn #t))
339     (let loop ((m music) (mods #f))
340       ;; The parser turns all sets, overrides etc into something
341       ;; wrapped in ContextSpeccedMusic.  If we ever get a set,
342       ;; override etc that is not wrapped in ContextSpeccedMusic, the
343       ;; user has created it in Scheme himself without providing the
344       ;; required wrapping.  In that case, using #f in the place of a
345       ;; context modification results in a reasonably recognizable
346       ;; error.
347       (if (music-is-of-type? m 'layout-instruction-event)
348           (ly:add-context-mod
349            mods
350            (case (ly:music-property m 'name)
351              ((PropertySet)
352               (list 'assign
353                     (ly:music-property m 'symbol)
354                     (ly:music-property m 'value)))
355              ((PropertyUnset)
356               (list 'unset
357                     (ly:music-property m 'symbol)))
358              ((OverrideProperty)
359               (cons* 'push
360                      (ly:music-property m 'symbol)
361                      (ly:music-property m 'grob-value)
362                      (cond
363                       ((ly:music-property m 'grob-property #f) => list)
364                       (else
365                        (ly:music-property m 'grob-property-path)))))
366              ((RevertProperty)
367               (cons* 'pop
368                      (ly:music-property m 'symbol)
369                      (cond
370                       ((ly:music-property m 'grob-property #f) => list)
371                       (else
372                        (ly:music-property m 'grob-property-path)))))))
373           (case (ly:music-property m 'name)
374             ((ApplyContext)
375              (ly:add-context-mod mods
376                                  (list 'apply
377                                        (ly:music-property m 'procedure))))
378             ((ContextSpeccedMusic)
379              ;; Use let* here to let defs catch up with modifications
380              ;; to the context defs made in the recursion
381              (let* ((mods (loop (ly:music-property m 'element)
382                                 (ly:make-context-mod)))
383                     (defs (ly:output-find-context-def
384                            output-def (ly:music-property m 'context-type))))
385                (if (null? defs)
386                    (ly:music-warning
387                     music
388                     (ly:format (_ "Cannot find context-def \\~a")
389                                (ly:music-property m 'context-type)))
390                    (for-each
391                     (lambda (entry)
392                       (ly:output-def-set-variable!
393                        output-def (car entry)
394                        (ly:context-def-modify (cdr entry) mods)))
395                     defs))))
396             (else
397              (let ((callback (ly:music-property m 'elements-callback)))
398                (if (procedure? callback)
399                    (fold loop mods (callback m))
400                    (if (and warn (ly:duration? (ly:music-property m 'duration)))
401                        (begin
402                          (ly:music-warning
403                           music
404                           (_ "Music unsuitable for output-def"))
405                          (set! warn #f))))))))
406       mods)))
407
408
409 ;;;;;;;;;;;;;;;;
410 ;; alist
411
412 (define-public assoc-get ly:assoc-get)
413
414 (define-public chain-assoc-get ly:chain-assoc-get)
415
416 (define-public (uniqued-alist alist acc)
417   (if (null? alist) acc
418       (if (assoc (caar alist) acc)
419           (uniqued-alist (cdr alist) acc)
420           (uniqued-alist (cdr alist) (cons (car alist) acc)))))
421
422 (define-public (alist<? x y)
423   (string<? (symbol->string (car x))
424             (symbol->string (car y))))
425
426 (define (map-alist-vals func list)
427   "map FUNC over the vals of LIST, leaving the keys."
428   (if (null?  list)
429       '()
430       (cons (cons  (caar list) (func (cdar list)))
431             (map-alist-vals func (cdr list)))))
432
433 (define (map-alist-keys func list)
434   "map FUNC over the keys of an alist LIST, leaving the vals."
435   (if (null?  list)
436       '()
437       (cons (cons (func (caar list)) (cdar list))
438             (map-alist-keys func (cdr list)))))
439
440 (define-public (first-member members lst)
441   "Return first successful member (of member) from @var{members} in
442 @var{lst}."
443   (any (lambda (m) (member m lst)) members))
444
445 (define-public (first-assoc keys lst)
446   "Return first successful assoc of key from @var{keys} in @var{lst}."
447   (any (lambda (k) (assoc k lst)) keys))
448
449 (define-public (flatten-alist alist)
450   (if (null? alist)
451       '()
452       (cons (caar alist)
453             (cons (cdar alist)
454                   (flatten-alist (cdr alist))))))
455
456 (define-public (map-selected-alist-keys function keys alist)
457   "Return @var{alist} with @var{function} applied to all of the values
458 in list @var{keys}.
459
460 For example:
461 @example
462 @code{guile> (map-selected-alist-keys - '(a b) '((a . 1) (b . -2) (c . 3) (d . 4)))}
463 @code{((a . -1) (b . 2) (c . 3) (d . 4)}
464 @end example"
465   (define (map-selected-alist-keys-helper key alist)
466     (map
467      (lambda (pair)
468        (if (equal? key (car pair))
469            (cons key (function (cdr pair)))
470            pair))
471      alist))
472   (fold map-selected-alist-keys-helper alist keys))
473
474 ;;;;;;;;;;;;;;;;
475 ;; vector
476
477 (define-public (vector-for-each proc vec)
478   (do
479       ((i 0 (1+ i)))
480       ((>= i (vector-length vec)) vec)
481     (vector-set! vec i (proc (vector-ref vec i)))))
482
483 ;;;;;;;;;;;;;;;;
484 ;; hash
485
486 (define-public (hash-table->alist t)
487   (hash-fold acons '() t))
488
489 ;; todo: code dup with C++.
490 (define-safe-public (alist->hash-table lst)
491   "Convert alist to table"
492   (let ((m (make-hash-table (length lst))))
493     (for-each (lambda (k-v) (hashq-set! m (car k-v) (cdr k-v))) lst)
494     m))
495
496 ;;;;;;;;;;;;;;;;
497 ;; list
498
499 (define (functional-or . rest)
500   (any identity rest))
501
502 (define (functional-and . rest)
503   (every identity rest))
504
505 (define (split-list lst n)
506   "Split LST in N equal sized parts"
507
508   (define (helper todo acc-vector k)
509     (if (null? todo)
510         acc-vector
511         (begin
512           (if (< k 0)
513               (set! k (+ n k)))
514
515           (vector-set! acc-vector k (cons (car todo) (vector-ref acc-vector k)))
516           (helper (cdr todo) acc-vector (1- k)))))
517
518   (helper lst (make-vector n '()) (1- n)))
519
520 (define (list-element-index lst x)
521   (list-index (lambda (m) (equal? m x)) lst))
522
523 (define-public (count-list lst)
524   "Given @var{lst} as @code{(E1 E2 .. )}, return
525 @code{((E1 . 1) (E2 . 2) ... )}."
526   (map cons lst (iota (length lst) 1)))
527
528 (define-public (list-join lst intermediate)
529   "Put @var{intermediate} between all elts of @var{lst}."
530
531   (fold-right
532    (lambda (elem prev)
533      (if (pair? prev)
534          (cons  elem (cons intermediate prev))
535          (list elem)))
536    '() lst))
537
538 (define-public filtered-map filter-map)
539
540 (define-public (flatten-list x)
541   "Unnest list."
542   (let loop ((x x) (tail '()))
543     (cond ((list? x) (fold-right loop tail x))
544           ((not (pair? x)) (cons x tail))
545           (else (loop (car x) (loop (cdr x) tail))))))
546
547 (define (list-minus a b)
548   "Return list of elements in A that are not in B."
549   (lset-difference eq? a b))
550
551 (define-public (uniq-list lst)
552   "Uniq @var{lst}, assuming that it is sorted.  Uses @code{equal?}
553 for comparisons."
554
555   (reverse!
556    (fold (lambda (x acc)
557            (if (null? acc)
558                (list x)
559                (if (equal? x (car acc))
560                    acc
561                    (cons x acc))))
562          '() lst) '()))
563
564 (define (split-at-predicate pred lst)
565   "Split LST into two lists at the first element that returns #f for
566   (PRED previous_element element).  Return the two parts as a pair.
567   Example: (split-at-predicate < '(1 2 3 2 1)) ==> ((1 2 3) . (2 1))"
568   (let ((i (and (pair? lst)
569                 (list-index (lambda (x y) (not (pred x y)))
570                             lst
571                             (cdr lst)))))
572     (if i
573         (call-with-values
574             (lambda () (split-at lst (1+ i)))
575           cons)
576         (list lst))))
577
578 (define-public (split-list-by-separator lst pred)
579   "Split @var{lst} at each element that satisfies @var{pred}, and return
580 the parts (with the separators removed) as a list of lists.  For example,
581 executing @samp{(split-list-by-separator '(a 0 b c 1 d) number?)} returns
582 @samp{((a) (b c) (d))}."
583   (call-with-values (lambda () (break pred lst))
584     (lambda (head tail)
585       (cons head
586             (if (null? tail)
587                 tail
588                 (split-list-by-separator (cdr tail) pred))))))
589
590 (define-public (offset-add a b)
591   (cons (+ (car a) (car b))
592         (+ (cdr a) (cdr b))))
593
594 (define-public (offset-flip-y o)
595   (cons (car o) (- (cdr o))))
596
597 (define-public (offset-scale o scale)
598   (cons (* (car o) scale)
599         (* (cdr o) scale)))
600
601 (define-public (ly:list->offsets accum coords)
602   (if (null? coords)
603       accum
604       (cons (cons (car coords) (cadr coords))
605             (ly:list->offsets accum (cddr coords)))))
606
607 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
608 ;; intervals
609
610 (define-public empty-interval '(+inf.0 . -inf.0))
611
612 (define-public (symmetric-interval expr)
613   (cons (- expr) expr))
614
615 (define-public (interval-length x)
616   "Length of the number-pair @var{x}, if an interval."
617   (max 0 (- (cdr x) (car x))))
618
619 (define-public (ordered-cons a b)
620   (cons (min a b)
621         (max a b)))
622
623 (define-public (interval-bound interval dir)
624   ((if (= dir RIGHT) cdr car) interval))
625
626 (define-public (interval-index interval dir)
627   "Interpolate @var{interval} between between left (@var{dir}=-1) and
628 right (@var{dir}=+1)."
629
630   (* (+  (interval-start interval) (interval-end interval)
631          (* dir (- (interval-end interval) (interval-start interval))))
632      0.5))
633
634 (define-public (interval-center x)
635   "Center the number-pair @var{x}, if an interval."
636   (if (interval-empty? x)
637       0.0
638       (/ (+ (car x) (cdr x)) 2)))
639
640 (define-public interval-start car)
641
642 (define-public interval-end cdr)
643
644 (define (other-axis a)
645   (remainder (+ a 1) 2))
646
647 (define-public (interval-scale iv factor)
648   (cons (* (car iv) factor)
649         (* (cdr iv) factor)))
650
651 (define-public (interval-widen iv amount)
652   (cons (- (car iv) amount)
653         (+ (cdr iv) amount)))
654
655 (define-public (interval-empty? iv)
656   (> (car iv) (cdr iv)))
657
658 (define-public (interval-union i1 i2)
659   (cons
660    (min (car i1) (car i2))
661    (max (cdr i1) (cdr i2))))
662
663 (define-public (interval-intersection i1 i2)
664   (cons
665    (max (car i1) (car i2))
666    (min (cdr i1) (cdr i2))))
667
668 (define-public (interval-sane? i)
669   (not (or  (nan? (car i))
670             (inf? (car i))
671             (nan? (cdr i))
672             (inf? (cdr i))
673             (> (car i) (cdr i)))))
674
675 (define-public (add-point interval p)
676   (cons (min (interval-start interval) p)
677         (max (interval-end interval) p)))
678
679 (define-public (reverse-interval iv)
680   (cons (cdr iv) (car iv)))
681
682 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
683 ;; coordinates
684
685 (define coord-x car)
686 (define coord-y cdr)
687
688 (define (coord-operation operator operand coordinate)
689   (if (pair? operand)
690       (cons (operator (coord-x operand) (coord-x coordinate))
691             (operator (coord-y operand) (coord-y coordinate)))
692       (cons (operator operand (coord-x coordinate))
693             (operator operand (coord-y coordinate)))))
694
695 (define (coord-apply function coordinate)
696   (if (pair? function)
697       (cons
698        ((coord-x function) (coord-x coordinate))
699        ((coord-y function) (coord-y coordinate)))
700       (cons
701        (function (coord-x coordinate))
702        (function (coord-y coordinate)))))
703
704 (define-public (coord-translate coordinate amount)
705   (coord-operation + amount coordinate))
706
707 (define-public (coord-scale coordinate amount)
708   (coord-operation * amount coordinate))
709
710 (define-public (coord-rotate coordinate angle-in-radians)
711   ;; getting around (sin PI) not being exactly zero by switching to cos at
712   ;; appropiate angles and/or taking the negative value (vice versa for cos)
713   (let* ((quadrant (inexact->exact (round (/ angle-in-radians (/ PI 2)))))
714          (moved-angle (- angle-in-radians (* quadrant (/ PI 2))))
715          (s (sin moved-angle))
716          (c (cos moved-angle))
717          (x (coord-x coordinate))
718          (y (coord-y coordinate)))
719     (case (modulo quadrant 4)
720       ((0) ;; -45 .. 45
721        (cons (- (* c x) (* s y))
722              (+ (* s x) (* c y))))
723       ((1) ;; 45 .. 135
724        (cons (- (* (- s) x) (* c y))
725              (+ (* c x) (* (- s) y))))
726       ((2) ;; 135 .. 225
727        (cons (- (* (- c) x) (* (- s) y))
728              (+ (* (- s) x) (* (- c) y))))
729       ((3) ;; 225 .. 315
730        (cons (- (* s x) (* (- c) y))
731              (+ (* (- c) x) (* s y))))
732       ;; for other angles (modulo quadrant 4) returns one of the above cases
733        )))
734
735 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
736 ;; trig
737
738 (define-public PI (* 4 (atan 1)))
739
740 (define-public TWO-PI (* 2 PI))
741
742 (define-public PI-OVER-TWO (/ PI 2))
743
744 (define-public THREE-PI-OVER-TWO (* 3 PI-OVER-TWO))
745
746 (define-public (cyclic-base-value value cycle)
747   "Take @var{value} and modulo-maps it between 0 and base @var{cycle}."
748   (cond ((< value 0)
749          (cyclic-base-value (+ value cycle) cycle))
750         ((>= value cycle)
751          (cyclic-base-value (- value cycle) cycle))
752         (else value)))
753
754 (define-public (angle-0-2pi angle)
755   "Take @var{angle} (in radians) and maps it between 0 and 2pi."
756   (cyclic-base-value angle TWO-PI))
757
758 (define-public (angle-0-360 angle)
759   "Take @var{angle} (in degrees) and maps it between 0 and 360 degrees."
760   (cyclic-base-value angle 360.0))
761
762 (define-public PI-OVER-180  (/ PI 180))
763
764 (define-public (degrees->radians angle-degrees)
765   "Convert the given angle from degrees to radians."
766   (* angle-degrees PI-OVER-180))
767
768 (define-public (ellipse-radius x-radius y-radius angle)
769   (/
770    (* x-radius y-radius)
771    (sqrt
772     (+ (* (expt y-radius 2)
773           (* (cos angle) (cos angle)))
774        (* (expt x-radius 2)
775           (* (sin angle) (sin angle)))))))
776
777 (define-public (polar->rectangular radius angle-in-degrees)
778   "Return polar coordinates (@var{radius}, @var{angle-in-degrees})
779 as rectangular coordinates @code{(x-length . y-length)}."
780   (ly:directed angle-in-degrees radius))
781
782 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
783 ;; string
784
785 (define-public (string-endswith s suffix)
786   (equal? suffix (substring s
787                             (max 0 (- (string-length s) (string-length suffix)))
788                             (string-length s))))
789
790 (define-public (string-startswith s prefix)
791   (equal? prefix (substring s 0 (min (string-length s) (string-length prefix)))))
792
793 (define-public (remove-whitespace strg)
794 "Remove characters satisfying @code{char-whitespace?} from string @var{strg}"
795   (string-delete
796     strg
797     char-whitespace?))
798
799 (define-public (string-encode-integer i)
800   (cond
801    ((= i  0) "o")
802    ((< i 0)   (string-append "n" (string-encode-integer (- i))))
803    (else (string-append
804           (make-string 1 (integer->char (+ 65 (modulo i 26))))
805           (string-encode-integer (quotient i 26))))))
806
807 (define (number->octal-string x)
808   (let* ((n (inexact->exact x))
809          (n64 (quotient n 64))
810          (n8 (quotient (- n (* n64 64)) 8)))
811     (string-append
812      (number->string n64)
813      (number->string n8)
814      (number->string (remainder (- n (+ (* n64 64) (* n8 8))) 8)))))
815
816 (define-public (ly:inexact->string x radix)
817   (let ((n (inexact->exact x)))
818     (number->string n radix)))
819
820 (define-public (ly:number-pair->string c)
821   (string-append (ly:number->string (car c)) " "
822                  (ly:number->string (cdr c))))
823
824 (define-public (dir-basename file . rest)
825   "Strip suffixes in @var{rest}, but leave directory component for
826 @var{file}."
827   (define (inverse-basename x y) (basename y x))
828   (simple-format #f "~a/~a" (dirname file)
829                  (fold inverse-basename file rest)))
830
831 (define-public (write-me message x)
832   "Return @var{x}.  Display @var{message} and write @var{x}.
833 Handy for debugging, possibly turned off."
834   (display message) (write x) (newline) x)
835 ;;  x)
836
837 (define-public (stderr string . rest)
838   (apply format (current-error-port) string rest)
839   (force-output (current-error-port)))
840
841 (define-public (debugf string . rest)
842   (if #f
843       (apply stderr string rest)))
844
845 (define (index-cell cell dir)
846   (if (equal? dir 1)
847       (cdr cell)
848       (car cell)))
849
850 (define (cons-map f x)
851   "map F to contents of X"
852   (cons (f (car x)) (f (cdr x))))
853
854 (define-public (list-insert-separator lst between)
855   "Create new list, inserting @var{between} between elements of @var{lst}."
856   (define (conc x y )
857     (if (eq? y #f)
858         (list x)
859         (cons x  (cons between y))))
860   (fold-right conc #f lst))
861
862 (define-public (string-regexp-substitute a b str)
863   (regexp-substitute/global #f a str 'pre b 'post))
864
865 (define (regexp-split str regex)
866   (define matches '())
867   (define end-of-prev-match 0)
868   (define (notice match)
869
870     (set! matches (cons (substring (match:string match)
871                                    end-of-prev-match
872                                    (match:start match))
873                         matches))
874     (set! end-of-prev-match (match:end match)))
875
876   (regexp-substitute/global #f regex str notice 'post)
877
878   (if (< end-of-prev-match (string-length str))
879       (set!
880        matches
881        (cons (substring str end-of-prev-match (string-length str)) matches)))
882
883   (reverse matches))
884
885 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
886 ;; numbering styles
887
888 (define-public (number-format number-type num . custom-format)
889   "Print NUM accordingly to the requested NUMBER-TYPE.
890 Choices include @code{roman-lower} (by default),
891 @code{roman-upper}, @code{arabic} and @code{custom}.
892 In the latter case, CUSTOM-FORMAT must be supplied
893 and will be applied to NUM."
894  (cond
895    ((equal? number-type 'roman-lower)
896     (fancy-format #f "~(~@r~)" num))
897    ((equal? number-type 'roman-upper)
898     (fancy-format #f "~@r" num))
899    ((equal? number-type 'arabic)
900     (fancy-format #f "~d" num))
901    ((equal? number-type 'custom)
902     (fancy-format #f (car custom-format) num))
903    (else (fancy-format #f "~(~@r~)" num))))
904
905 ;;;;;;;;;;;;;;;;
906 ;; other
907
908 (define (sign x)
909   (if (= x 0)
910       0
911       (if (< x 0) -1 1)))
912
913 (define-public (binary-search start end getter target-val)
914   (_i "Find the index between @var{start} and @var{end} (an integer)
915 which produces the closest match to @var{target-val} if
916 applied to function @var{getter}.")
917   (if (<= end start)
918       start
919       (let* ((compare (quotient (+ start end) 2))
920              (get-val (getter compare)))
921         (cond
922          ((< target-val get-val)
923           (set! end (1- compare)))
924          ((< get-val target-val)
925           (set! start (1+ compare))))
926         (binary-search start end getter target-val))))
927
928 (define-public (car< a b)
929   (< (car a) (car b)))
930
931 (define-public (car<= a b)
932   (<= (car a) (car b)))
933
934 (define-public (symbol<? lst r)
935   (string<? (symbol->string lst) (symbol->string r)))
936
937 (define-public (symbol-key<? lst r)
938   (string<? (symbol->string (car lst)) (symbol->string (car r))))
939
940 (define-public (eval-carefully symbol module . default)
941   "Check whether all symbols in expr @var{symbol} are reachable
942 in module @var{module}.  In that case evaluate, otherwise
943 print a warning and set an optional @var{default}."
944   (let* ((unavailable? (lambda (sym)
945                          (not (module-defined? module sym))))
946          (sym-unavailable
947           (filter
948            unavailable?
949            (filter symbol? (flatten-list symbol)))))
950     (if (null? sym-unavailable)
951         (eval symbol module)
952         (let* ((def (and (pair? default) (car default))))
953           (ly:programming-error
954            "cannot evaluate ~S in module ~S, setting to ~S"
955            (object->string symbol)
956            (object->string module)
957            (object->string def))
958           def))))
959
960 (define (self-evaluating? x)
961   (or (number? x) (string? x) (procedure? x) (boolean? x)))
962
963 (define (ly-type? x)
964   (any (lambda (p) ((car p) x)) lilypond-exported-predicates))
965
966 (define-public (pretty-printable? val)
967   (and (not (self-evaluating? val))
968        (not (symbol? val))
969        (not (hash-table? val))
970        (not (ly-type? val))))
971
972 (define-public (scm->string val)
973   (let* ((quote-style (if (string? val)
974                         'double
975                         (if (or (null? val) ; (ly-type? '()) => #t
976                                 (and (not (self-evaluating? val))
977                                      (not (vector? val))
978                                      (not (hash-table? val))
979                                      (not (ly-type? val))))
980                           'single
981                           'none)))
982          ; don't confuse users with #<procedure ...> syntax
983          (str (if (and (procedure? val)
984                        (symbol? (procedure-name val)))
985                 (symbol->string (procedure-name val))
986                 (call-with-output-string
987                   (if (pretty-printable? val)
988                     ; property values in PDF hit margin after 64 columns
989                     (lambda (port)
990                       (pretty-print val port #:width (case quote-style
991                                                        ((single) 63)
992                                                        (else 64))))
993                     (lambda (port) (display val port)))))))
994     (case quote-style
995       ((single) (string-append
996                   "'"
997                   (string-regexp-substitute "\n " "\n  " str)))
998       ((double) (string-append "\"" str "\""))
999       (else str))))
1000
1001 (define-public (!= lst r)
1002   (not (= lst r)))
1003
1004 (define-public lily-unit->bigpoint-factor
1005   (cond
1006    ((equal? (ly:unit) "mm") (/ 72.0 25.4))
1007    ((equal? (ly:unit) "pt") (/ 72.0 72.27))
1008    (else (ly:error (_ "unknown unit: ~S") (ly:unit)))))
1009
1010 (define-public lily-unit->mm-factor
1011   (* 25.4 (/ lily-unit->bigpoint-factor 72)))
1012
1013 ;;; FONT may be font smob, or pango font string...
1014 (define-public (font-name-style font)
1015   (if (string? font)
1016       (string-downcase font)
1017       (let* ((font-name (ly:font-name font))
1018              (full-name (if font-name font-name (ly:font-file-name font))))
1019         (string-downcase full-name))))
1020
1021 (define-public (modified-font-metric-font-scaling font)
1022   (let* ((designsize (ly:font-design-size font))
1023          (magnification (* (ly:font-magnification font)))
1024          (scaling (* magnification designsize)))
1025     (debugf "scaling:~S\n" scaling)
1026     (debugf "magnification:~S\n" magnification)
1027     (debugf "design:~S\n" designsize)
1028     scaling))
1029
1030 (define-public (version-not-seen-message input-file-name)
1031   (ly:warning-located
1032    (ly:format "~a:1" input-file-name)
1033    (_ "no \\version statement found, please add~afor future compatibility")
1034    (format #f "\n\n\\version ~s\n\n" (lilypond-version))))
1035
1036 (define-public (output-module? module)
1037   "Returns @code{#t} if @var{module} belongs to an output module
1038 usually carrying context definitions (@code{\\midi} or
1039 @code{\\layout})."
1040   (or (module-ref module 'is-midi #f)
1041       (module-ref module 'is-layout #f)))