]> git.donarmstrong.com Git - lilypond.git/blob - scm/page-layout.scm
dea8df39025fa29aaaab5702b016edf76454b0d9
[lilypond.git] / scm / page-layout.scm
1 ;;;; page-layout.scm -- page breaking and page layout
2 ;;;;
3 ;;;;  source file of the GNU LilyPond music typesetter
4 ;;;;
5 ;;;; (c) 2004 Jan Nieuwenhuizen <janneke@gnu.org>
6 ;;;;          Han-Wen Nienhuys <hanwen@cs.uu.nl>
7
8 (use-modules (oop goops describe)
9              (oop goops))
10
11
12 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
13
14 (define-class <optimally-broken-page-node> ()
15   (prev #:init-value '() #:accessor node-prev #:init-keyword #:prev)
16   (page #:init-value 0 #:accessor node-page-number #:init-keyword #:pageno)
17   (force #:init-value 0 #:accessor node-force #:init-keyword #:force) 
18   (penalty #:init-value 0 #:accessor node-penalty #:init-keyword #:penalty)
19   (configuration #:init-value '() #:accessor node-configuration #:init-keyword #:configuration)
20   (lines #:init-value 0 #:accessor node-lines #:init-keyword #:lines))
21
22 (define-method (display (node <optimally-broken-page-node>) port)
23   (map (lambda (x) (display x port))
24        (list
25         "Page " (node-page-number node)
26         " Lines: " (node-lines node)
27         " Penalty " (node-penalty node)
28         "\n")))
29
30 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
31
32 (define TAGLINE
33   (string-append "Engraved by LilyPond (version " (lilypond-version) ")"))
34
35 (define (page-headfoot layout scopes number sym sepsym dir last?)
36   "Create a stencil including separating space."
37   (let* ((header-proc (ly:output-def-lookup layout sym))
38        (sep (ly:output-def-lookup layout sepsym))
39        (stencil (ly:make-stencil "" '(0 . 0) '(0 . 0)))
40        (head-stencil
41         (if (procedure? header-proc)
42             (header-proc layout scopes number last?)
43             #f)))
44
45     (if (and (number? sep)
46              (ly:stencil? head-stencil)
47              (not (ly:stencil-empty? head-stencil)))
48         (set! head-stencil
49               (ly:stencil-combine-at-edge
50                stencil Y  dir head-stencil
51                sep 0.0)))
52
53     head-stencil))
54
55 (define-public (default-page-music-height layout scopes number last?)
56   "Printable area for music and titles; matches default-page-make-stencil." 
57   (let* ((h (- (ly:output-def-lookup layout 'vsize)
58              (ly:output-def-lookup layout 'topmargin)
59              (ly:output-def-lookup layout 'bottommargin)))
60        (head (page-headfoot layout scopes number 'make-header 'headsep UP last?))
61        (foot (page-headfoot layout scopes number 'make-footer 'footsep DOWN last?))
62        (available 
63         (- h (if (ly:stencil? head)
64                  (interval-length (ly:stencil-extent head Y))
65                  0)
66            (if (ly:stencil? foot)
67                (interval-length (ly:stencil-extent foot Y))
68                0))))
69     
70                                         ;    (display (list "\n available" available head foot))
71     available))
72
73 (define-public (default-page-make-stencil
74                  lines offsets layout scopes number last? )
75   "Construct a stencil representing the page from LINES.
76
77  Offsets is a list of increasing numbers. They must be negated to
78 create offsets.
79  "
80   (let* ((topmargin  (ly:output-def-lookup layout 'topmargin))
81        
82        ;; TODO: naming vsize/hsize not analogous to TeX.
83        
84        (vsize (ly:output-def-lookup layout 'vsize))
85        (hsize (ly:output-def-lookup layout 'hsize))
86
87        (system-separator-markup (ly:output-def-lookup layout 'systemSeparatorMarkup))
88        (system-separator-stencil (if (markup? system-separator-markup)
89                                      (interpret-markup layout
90                                                        (page-properties layout)
91                                                        system-separator-markup)
92                                      #f))
93        (lmargin (ly:output-def-lookup layout 'leftmargin))
94        (leftmargin (if lmargin
95                        lmargin
96                        (/ (- hsize
97                              (ly:output-def-lookup layout 'linewidth)) 2)))
98
99        (rightmargin (ly:output-def-lookup layout 'rightmargin))
100        (bottom-edge (- vsize
101                        (ly:output-def-lookup layout 'bottommargin)))
102        
103        (head (page-headfoot layout scopes number 'make-header 'headsep UP last?))
104        (foot (page-headfoot layout scopes number 'make-footer 'footsep DOWN last?))
105
106        (head-height (if (ly:stencil? head)
107                         (interval-length (ly:stencil-extent head Y))
108                         0.0))
109
110        (height-proc (ly:output-def-lookup layout 'page-music-height))
111
112        (page-stencil (ly:make-stencil '()
113                                       (cons leftmargin hsize)
114                                       (cons (- topmargin) 0)))
115        (last-system #f)
116        (last-y 0.0)
117        (add-to-page (lambda (stencil y)
118                       (set! page-stencil
119                             (ly:stencil-add page-stencil
120                                             (ly:stencil-translate-axis stencil
121                                              (- 0 head-height y topmargin) Y)
122                                             ))))
123        (add-system (lambda (stencil-position)
124                      (let*
125                          ((system (car stencil-position))
126                           (stencil (ly:paper-system-stencil system))
127                           (y (cadr stencil-position))
128                           (is-title (ly:paper-system-title?
129                                      (car stencil-position))))
130
131                     
132                        (add-to-page stencil y)
133                        (if (and (ly:stencil? system-separator-stencil)
134                                 last-system
135                                 (not (ly:paper-system-title? system))
136                                 (not (ly:paper-system-title? last-system)))
137                            (add-to-page system-separator-stencil
138                                         (average (- last-y
139                                                     (car (ly:paper-system-staff-extents last-system)))
140                                                  (- y
141                                                     (cdr (ly:paper-system-staff-extents system))))))
142                        (set! last-system system)
143                        (set! last-y y)
144                        ))))
145
146     (if #f
147         (display (list
148                   "leftmargin" leftmargin "rightmargin" rightmargin)))
149     
150     (set! page-stencil (ly:stencil-combine-at-edge
151                         page-stencil Y DOWN head 0. 0.))
152
153     (map add-system (zip lines offsets))
154     (if (ly:stencil? foot)
155         (set! page-stencil
156               (ly:stencil-add
157                page-stencil
158                (ly:stencil-translate
159                 foot
160                 (cons 0
161                       (+ (- bottom-edge)
162                          (- (car (ly:stencil-extent foot Y)))))))))
163
164     (ly:stencil-translate page-stencil (cons leftmargin 0))))
165
166
167
168
169 ;;; optimal page breaking
170
171 ;;; This is not optimal page breaking, this is optimal distribution of
172 ;;; lines over pages; line breaks are a given.
173
174                                         ; TODO:
175                                         ;
176                                         ; - density scoring
177                                         ; - separate function for word-wrap style breaking?
178                                         ; - raggedbottom? raggedlastbottom? 
179
180 (define-public (ly:optimal-page-breaks
181                 lines paper-book)
182   "Return pages as a list starting with 1st page. Each page is a list
183 of lines. "
184
185
186   (define MAXPENALTY 1e9)
187   (define paper (ly:paper-book-paper paper-book))
188   (define scopes (ly:paper-book-scopes paper-book))
189
190   (define (page-height page-number last?)
191     (let ((p (ly:output-def-lookup paper 'page-music-height)))
192
193       (if (procedure? p)
194           (p paper scopes page-number last?)
195           10000)))
196   
197   (define (get-path node done)
198     "Follow NODE.PREV, and return as an ascending list of pages. DONE
199 is what have collected so far, and has ascending page numbers."
200     
201     (if (is-a? node <optimally-broken-page-node>)
202         (get-path (node-prev node) (cons node done))
203         done))
204
205   (define (combine-penalties force user best-paths)
206     (let* ((prev-force  (if (null? best-paths)
207                           0.0
208                           (node-force  (car best-paths))))
209          (prev-penalty (if (null? best-paths)
210                            0.0
211                            (node-penalty (car best-paths))))
212          (inter-system-space (ly:output-def-lookup paper 'betweensystemspace))
213          (force-equalization-factor 0.3)
214          (relative-force (/ force inter-system-space))
215          (abs-relative-force (abs relative-force)))
216       
217       
218       (+ (* abs-relative-force (+ abs-relative-force 1))
219          prev-penalty
220          (* force-equalization-factor (/ (abs (- prev-force force)) inter-system-space))
221          user)))
222
223   (define (space-systems page-height lines ragged?)
224     (let* ((inter-system-space
225           (ly:output-def-lookup paper 'betweensystemspace))
226          (system-vector (list->vector
227                          (append lines
228                                  (if (= (length lines) 1)
229                                      '(#f)
230                                      '()))))
231
232          (staff-extents
233           (list->vector
234            (append  (map
235                      ly:paper-system-staff-extents
236                      lines)
237                     (if (= (length lines) 1)
238                         '((0 .  0))
239                         '()))))
240          (real-extents
241           (list->vector
242            (append
243             (map
244              (lambda (sys) (ly:paper-system-extent sys Y)) lines)
245             (if (= (length lines) 1)
246                 '((0 .  0))
247                 '()))))
248          (no-systems (vector-length real-extents))
249          (topskip (interval-end (vector-ref real-extents 0)))
250          (space-left (- page-height
251                         (apply + (map interval-length (vector->list real-extents)))))
252          
253          (space (- page-height
254                    topskip
255                    (-  (interval-start (vector-ref real-extents (1- no-systems))))))
256
257          (fixed-dist (ly:output-def-lookup paper 'betweensystempadding))
258          (calc-spring
259           (lambda (idx)
260             (let* ((this-system-ext (vector-ref staff-extents idx))
261                  (next-system-ext (vector-ref staff-extents (1+ idx)))
262                  (fixed (max 0  (- (+ (interval-end next-system-ext)
263                                       fixed-dist)
264                                    (interval-start this-system-ext))))
265                  (title1? (and (vector-ref system-vector idx)
266                                (ly:paper-system-title? (vector-ref system-vector idx))))
267                  (title2? (and
268                            (vector-ref system-vector (1+ idx))
269                            (ly:paper-system-title? (vector-ref system-vector (1+ idx)))))
270                  (ideal (+
271                          (cond
272                           ((and title2? title1?)
273                            (ly:output-def-lookup paper 'betweentitlespace))
274                           (title1?
275                            (ly:output-def-lookup paper 'aftertitlespace))
276                           (title2?
277                            (ly:output-def-lookup paper 'beforetitlespace))
278                           (else inter-system-space))
279                          fixed))
280                  (hooke (/ 1 (- ideal fixed))))
281               (list ideal hooke))))
282
283          (springs (map calc-spring (iota (1- no-systems))))
284          (calc-rod
285           (lambda (idx)
286             (let* ((this-system-ext (vector-ref real-extents idx))
287                  (next-system-ext (vector-ref real-extents (1+ idx)))
288                  (distance (max  (- (+ (interval-end next-system-ext)
289                                        fixed-dist)
290                                     (interval-start this-system-ext)
291                                     ) 0)) 
292                  (entry (list idx (1+ idx) distance)))
293               entry)))
294          (rods (map calc-rod (iota (1- no-systems))))
295
296          ;; we don't set ragged based on amount space left.
297          ;; raggedbottomlast = ##T is much more predictable
298          (result (ly:solve-spring-rod-problem
299                   springs rods space
300                   ragged?))
301
302          (force (car result))
303          (positions
304           (map (lambda (y)
305                  (+ y topskip)) 
306                (cdr  result))))
307       
308       (if #f ;; debug.
309           (begin
310             (display (list "\n# systems: " no-systems
311                            "\nreal-ext" real-extents "\nstaff-ext" staff-extents
312                            "\ninterscore" inter-system-space
313                            "\nspace-letf" space-left
314                            "\nspring,rod" springs rods
315                            "\ntopskip " topskip
316                            " space " space
317                            "\npage-height" page-height
318                            "\nragged" ragged?
319                            "\nforce" force
320                            "\nres" (cdr result)
321                            "\npositions" positions "\n"))))
322       
323       (cons force positions)))
324   
325   (define (walk-paths done-lines best-paths current-lines  last? current-best)
326     "Return the best optimal-page-break-node that contains
327 CURRENT-LINES.  DONE-LINES.reversed ++ CURRENT-LINES is a consecutive
328 ascending range of lines, and BEST-PATHS contains the optimal breaks
329 corresponding to DONE-LINES.
330
331 CURRENT-BEST is the best result sofar, or #f."
332     
333     (let* ((this-page-num (if (null? best-paths)
334                               (ly:output-def-lookup paper 'firstpagenumber)
335                               (1+ (node-page-number (car best-paths)))))
336
337            (ragged-all? (eq? #t (ly:output-def-lookup paper 'raggedbottom)))
338            (ragged-last? (eq? #t (ly:output-def-lookup paper 'raggedlastbottom)))
339            (ragged? (or ragged-all? 
340                         (and ragged-last?
341                              last?)))
342            (page-height (page-height this-page-num last?))
343            (vertical-spacing (space-systems page-height current-lines ragged?))
344            (satisfied-constraints (car vertical-spacing))
345            (force (if satisfied-constraints
346                       (if (and last? ragged-last?)
347                           0.0
348                           satisfied-constraints)
349                       10000))
350            (positions (cdr vertical-spacing))
351            (user-nobreak-penalties
352             (-
353              (apply + (filter negative?
354                               (map ly:paper-system-break-before-penalty
355                                    (cdr current-lines))))))
356            (user-penalty
357             (+
358              (max (ly:paper-system-break-before-penalty (car current-lines)) 0.0)
359              user-nobreak-penalties))
360            (total-penalty (combine-penalties
361                            force user-penalty
362                            best-paths))
363
364            
365            (better? (or
366                      (not current-best)
367                      (< total-penalty (node-penalty current-best))))
368            (new-best (if better?
369                          (make <optimally-broken-page-node>
370                            #:prev  (if (null? best-paths)
371                                        #f
372                                        (car best-paths))
373                            #:lines current-lines
374                            #:pageno this-page-num
375                            #:force force
376                            #:configuration positions
377                            #:penalty total-penalty)
378                          current-best)))
379       
380       (if #f ;; debug
381           (display
382            (list
383             "\nuser pen " user-penalty
384             "\nsatisfied-constraints" satisfied-constraints
385             "\nlast? " last? "ragged?" ragged?
386             "\nbetter? " better? " total-penalty " total-penalty "\n"
387             "\nconfig " positions
388             "\nforce " force
389             "\nlines: " current-lines "\n")))
390
391       (if #f ; debug
392           (display (list "\nnew-best is " (node-lines new-best)
393                          "\ncontinuation of "
394                          (if (null? best-paths)
395                              "start"
396                              (node-lines (car best-paths))))))
397       
398       (if (and (pair? done-lines)
399                ;; if this page is too full, adding another line won't help
400                satisfied-constraints)
401           (walk-paths (cdr done-lines) (cdr best-paths)
402                       (cons (car done-lines) current-lines)
403                       last? new-best)
404           
405           new-best)))
406
407   (define (walk-lines done best-paths todo)
408     "Return the best page breaking as a single
409 <optimal-page-break-node> for optimally breaking TODO ++
410 DONE.reversed. BEST-PATHS is a list of break nodes corresponding to
411 DONE."
412     (if (null? todo)
413         (car best-paths)
414         (let* ((this-line (car todo))
415                (last? (null? (cdr todo)))
416                (next (walk-paths done best-paths (list this-line) last? #f)))
417
418                                         ;         (display "\n***************")
419           (walk-lines (cons this-line done)
420                       (cons next best-paths)
421                       (cdr todo)))))
422
423   (define (line-number node)
424     (ly:paper-system-number (car (node-lines node))))
425
426   (let* ((best-break-node (walk-lines '() '() lines))
427          (break-nodes (get-path best-break-node '())))
428
429     (if #f; (ly:get-option 'verbose)
430         (begin
431           (display (list
432                     "\nbreaks: " (map line-number break-nodes))
433                    "\nsystems " (map node-lines break-nodes)
434                    "\npenalties " (map node-penalty break-nodes)
435                    "\nconfigs " (map node-configuration break-nodes))))
436
437     
438                                         ; create stencils.
439     
440     (map (lambda (node)
441            ((ly:output-def-lookup paper 'page-make-stencil)
442             (node-lines node)
443             (node-configuration node)
444             paper
445             scopes
446             (node-page-number node)
447             (eq? node best-break-node)))
448          break-nodes)))
449
450