r3767: Auto commit for Debian build
[cl-base64.git] / encode.lisp
1 ;;;; -*- Mode: Lisp; Syntax: ANSI-Common-Lisp; Base: 10 -*-
2 ;;;; *************************************************************************
3 ;;;; FILE IDENTIFICATION
4 ;;;;
5 ;;;; Name:          encode.lisp
6 ;;;; Purpose:       cl-base64 encoding routines
7 ;;;; Programmer:    Kevin M. Rosenberg
8 ;;;; Date Started:  Dec 2002
9 ;;;;
10 ;;;; $Id: encode.lisp,v 1.4 2003/01/14 11:43:10 kevin Exp $
11 ;;;;
12 ;;;; This file implements the Base64 transfer encoding algorithm as
13 ;;;; defined in RFC 1521 by Borensten & Freed, September 1993.
14 ;;;; See: http://www.ietf.org/rfc/rfc1521.txt
15 ;;;;
16 ;;;; Based on initial public domain code by Juri Pakaste <juri@iki.fi>
17 ;;;;
18 ;;;; Copyright 2002-2003 Kevin M. Rosenberg
19 ;;;; Permission to use with BSD-style license included in the COPYING file
20 ;;;; *************************************************************************
21
22 (declaim (optimize (debug 3) (speed 3) (safety 1) (compilation-speed 0)))
23
24 ;;;; Extended by Kevin M. Rosenberg <kevin@rosenberg.net>:
25 ;;;;   - .asd file
26 ;;;;   - numerous speed optimizations
27 ;;;;   - conversion to and from integers
28 ;;;;   - Renamed functions now that supporting integer conversions
29 ;;;;   - URI-compatible encoding using :uri key
30 ;;;;
31 ;;;; $Id: encode.lisp,v 1.4 2003/01/14 11:43:10 kevin Exp $
32
33 (in-package #:cl-base64)
34
35
36 (defun round-next-multiple (x n)
37   "Round x up to the next highest multiple of n."
38   (declare (fixnum n)
39            (optimize (speed 3)))
40   (let ((remainder (mod x n)))
41     (declare (fixnum remainder))
42     (if (zerop remainder)
43         x
44         (the fixnum (+ x (the fixnum (- n remainder)))))))
45
46 (defmacro def-*-to-base64-* (input-type output-type)
47   `(defun ,(intern (concatenate 'string (symbol-name input-type)
48                                 (symbol-name :-to-base64-)
49                                 (symbol-name output-type)))
50        (input
51         ,@(when (eq output-type :stream)
52                 '(output))
53         &key (uri nil) (columns 0))
54      "Encode a string array to base64. If columns is > 0, designates
55 maximum number of columns in a line and the string will be terminated
56 with a #\Newline."
57      (declare ,@(case input-type
58                       (:string
59                        '((string input)))
60                       (:usb8-array
61                        '((type (array (unsigned-byte 8) (*)) input))))
62               (fixnum columns)
63               (optimize (speed 3)))
64      (let ((pad (if uri *uri-pad-char* *pad-char*))
65            (encode-table (if uri *uri-encode-table* *encode-table*)))
66        (declare (simple-string encode-table)
67                 (character pad))
68        (let* ((string-length (length input))
69               (complete-group-count (truncate string-length 3))
70               (remainder (nth-value 1 (truncate string-length 3)))
71               (padded-length (* 4 (truncate (+ string-length 2) 3)))
72               ,@(when (eq output-type :string)
73                       '((num-lines (if (plusp columns)
74                                        (truncate (+ padded-length (1- columns)) columns)
75                                        0))
76                         (num-breaks (if (plusp num-lines)
77                                         (1- num-lines)
78                                         0))
79                         (strlen (+ padded-length num-breaks))
80                         (result (make-string strlen))
81                         (ioutput 0)))
82               (col (if (plusp columns)
83                        0
84                        (1+ padded-length))))
85          (declare (fixnum string-length padded-length col
86                           ,@(when (eq output-type :string)
87                                   '(ioutput)))
88                   ,@(when (eq output-type :string)
89                           '((simple-string result))))
90          (labels ((output-char (ch)
91                     (if (= col columns)
92                         (progn
93                           ,@(case output-type
94                                   (:stream
95                                    '((write-char #\Newline output)))
96                                  (:string
97                                   '((setf (schar result ioutput) #\Newline)
98                                     (incf ioutput))))
99                           (setq col 1))
100                      (incf col))
101                  ,@(case output-type
102                          (:stream
103                           '((write-char ch output)))
104                          (:string
105                           '((setf (schar result ioutput) ch)
106                             (incf ioutput)))))
107                (output-group (svalue chars)
108                  (declare (fixnum svalue chars))
109                  (output-char
110                   (schar encode-table
111                          (the fixnum
112                            (logand #x3f
113                                    (the fixnum (ash svalue -18))))))
114                  (output-char
115                   (schar encode-table
116                          (the fixnum
117                            (logand #x3f
118                                         (the fixnum (ash svalue -12))))))
119                  (if (> chars 2)
120                      (output-char
121                       (schar encode-table
122                              (the fixnum
123                                (logand #x3f
124                                        (the fixnum (ash svalue -6))))))
125                      (output-char pad))
126                    (if (> chars 3)
127                        (output-char
128                         (schar encode-table
129                                (the fixnum
130                                  (logand #x3f svalue))))
131                        (output-char pad))))
132         (do ((igroup 0 (1+ igroup))
133              (isource 0 (+ isource 3)))
134             ((= igroup complete-group-count)
135              (cond
136                ((= remainder 2)
137                 (output-group
138                  (the fixnum
139                      (+
140                       (the fixnum
141                         (ash
142                          ,(case input-type
143                                 (:string
144                                  '(char-code (the character (char input isource))))
145                                 (:usb8-array
146                                  '(the fixnum (aref input isource))))
147                          16))
148                       (the fixnum
149                         (ash
150                          ,(case input-type
151                                 (:string
152                                  '(char-code (the character (char input (1+ isource)))))
153                                 (:usb8-array
154                                  '(the fixnum (aref input (1+ isource)))))
155                          8))))
156                  3))
157                ((= remainder 1)
158                 (output-group
159                  (the fixnum
160                    (ash
161                     ,(case input-type
162                            (:string
163                             '(char-code (the character (char input isource))))
164                            (:usb8-array
165                             '(the fixnum (aref input isource))))
166                     16))
167                  2)))
168              ,(case output-type
169                     (:string
170                      'result)
171                     (:stream
172                      'output)))
173           (declare (fixnum igroup isource))
174           (output-group 
175            (the fixnum
176              (+
177               (the fixnum
178                 (ash
179                  (the fixnum
180                  ,(case input-type
181                         (:string
182                          '(char-code (the character (char input isource))))
183                         (:usb8-array
184                          '(aref input isource))))
185                  16))
186               (the fixnum
187                 (ash
188                  (the fixnum
189                    ,(case input-type
190                           (:string
191                            '(char-code (the character (char input (1+ isource)))))
192                         (:usb8-array
193                          '(aref input (1+ isource)))))
194                  8))
195               (the fixnum
196                 ,(case input-type
197                        (:string
198                         '(char-code (the character (char input (+ 2 isource)))))
199                        (:usb8-array
200                         '(aref input (+ 2 isource))))
201                 )))
202            4)))))))
203
204 (def-*-to-base64-* :string :string)
205 (def-*-to-base64-* :string :stream)
206 (def-*-to-base64-* :usb8-array :string)
207 (def-*-to-base64-* :usb8-array :stream)
208
209
210 (defun integer-to-base64-string (input &key (uri nil) (columns 0))
211   "Encode an integer to base64 format."
212   (declare (integer input)
213            (fixnum columns)
214            (optimize (speed 3)))
215   (let ((pad (if uri *uri-pad-char* *pad-char*))
216         (encode-table (if uri *uri-encode-table* *encode-table*)))
217     (declare (simple-string encode-table)
218              (character pad))
219     (let* ((input-bits (integer-length input))
220            (byte-bits (round-next-multiple input-bits 8))
221            (padded-bits (round-next-multiple byte-bits 6))
222            (remainder-padding (mod padded-bits 24))
223            (padding-bits (if (zerop remainder-padding)
224                              0
225                              (- 24 remainder-padding)))
226            (padding-chars (/ padding-bits 6))
227            (padded-length (/ (+ padded-bits padding-bits) 6))
228            (last-line-len (if (plusp columns)
229                               (- padded-length (* columns
230                                                   (truncate
231                                                    padded-length columns)))
232                               0))
233            (num-lines (if (plusp columns)
234                           (truncate (+ padded-length (1- columns)) columns)
235                           0))
236            (num-breaks (if (plusp num-lines)
237                            (1- num-lines)
238                            0))
239            (strlen (+ padded-length num-breaks))
240            (last-char (1- strlen))
241            (str (make-string strlen))
242            (col (if (zerop last-line-len)
243                      columns
244                     last-line-len)))
245       (declare (fixnum padded-length num-lines col last-char
246                        padding-chars last-line-len))
247       (unless (plusp columns)
248         (setq col -1)) ;; set to flag to optimize in loop
249       
250       (dotimes (i padding-chars)
251         (declare (fixnum i))
252         (setf (schar str (the fixnum (- last-char i))) pad))
253
254       (do* ((strpos (- last-char padding-chars) (1- strpos))
255             (int (ash input (/ padding-bits 3))))
256            ((minusp strpos)
257             str)
258         (declare (fixnum strpos) (integer int))
259         (cond
260           ((zerop col)
261            (setf (schar str strpos) #\Newline)
262            (setq col columns))
263           (t
264            (setf (schar str strpos)
265                  (schar encode-table (the fixnum (logand int #x3f))))
266            (setq int (ash int -6))
267            (decf col)))))))
268
269 (defun integer-to-base64-stream (input stream &key (uri nil) (columns 0))
270   "Encode an integer to base64 format."
271   (declare (integer input)
272            (fixnum columns)
273            (optimize (speed 3)))
274   (let ((pad (if uri *uri-pad-char* *pad-char*))
275         (encode-table (if uri *uri-encode-table* *encode-table*)))
276     (declare (simple-string encode-table)
277              (character pad))
278     (let* ((input-bits (integer-length input))
279            (byte-bits (round-next-multiple input-bits 8))
280            (padded-bits (round-next-multiple byte-bits 6))
281            (remainder-padding (mod padded-bits 24))
282            (padding-bits (if (zerop remainder-padding)
283                              0
284                              (- 24 remainder-padding)))
285            (padding-chars (/ padding-bits 6))
286            (padded-length (/ (+ padded-bits padding-bits) 6))
287            (strlen padded-length)
288            (nonpad-chars (- strlen padding-chars))
289            (last-nonpad-char (1- nonpad-chars))
290            (str (make-string strlen)))
291       (declare (fixnum padded-length last-nonpad-char))
292       (do* ((strpos 0 (1+ strpos))
293             (int (ash input (/ padding-bits 3)) (ash int -6))
294             (6bit-value (logand int #x3f) (logand int #x3f)))
295            ((= strpos nonpad-chars)
296             (let ((col 0))
297               (declare (fixnum col))
298               (dotimes (i nonpad-chars)
299                 (declare (fixnum i))
300                 (write-char (schar str i) stream)
301                 (when (plusp columns)
302                   (incf col)
303                   (when (= col columns)
304                     (write-char #\Newline stream)
305                     (setq col 0))))
306               (dotimes (ipad padding-chars)
307                 (declare (fixnum ipad))
308                 (write-char pad stream)
309                 (when (plusp columns)
310                   (incf col)
311                   (when (= col columns)
312                     (write-char #\Newline stream)
313                     (setq col 0)))))
314             stream)
315         (declare (fixnum 6bit-value strpos)
316                  (integer int))
317         (setf (schar str (- last-nonpad-char strpos))
318               (schar encode-table 6bit-value))
319         ))))
320