1 /*@ S-nail - a mail user agent derived from Berkeley Mail.
2  *@ MIME support functions.
3  *@ TODO Complete rewrite.
4  *
5  * Copyright (c) 2000-2004 Gunnar Ritter, Freiburg i. Br., Germany.
6  * Copyright (c) 2012 - 2020 Steffen (Daode) Nurpmeso <steffen@sdaoden.eu>.
7  * SPDX-License-Identifier: BSD-4-Clause
8  */
9 /*
10  * Copyright (c) 2000
11  * Gunnar Ritter.  All rights reserved.
12  *
13  * Redistribution and use in source and binary forms, with or without
14  * modification, are permitted provided that the following conditions
15  * are met:
16  * 1. Redistributions of source code must retain the above copyright
17  *    notice, this list of conditions and the following disclaimer.
18  * 2. Redistributions in binary form must reproduce the above copyright
19  *    notice, this list of conditions and the following disclaimer in the
20  *    documentation and/or other materials provided with the distribution.
21  * 3. All advertising materials mentioning features or use of this software
22  *    must display the following acknowledgement:
23  *    This product includes software developed by Gunnar Ritter
24  *    and his contributors.
25  * 4. Neither the name of Gunnar Ritter nor the names of his contributors
26  *    may be used to endorse or promote products derived from this software
27  *    without specific prior written permission.
28  *
29  * THIS SOFTWARE IS PROVIDED BY GUNNAR RITTER AND CONTRIBUTORS ``AS IS'' AND
30  * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
31  * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
32  * ARE DISCLAIMED.  IN NO EVENT SHALL GUNNAR RITTER OR CONTRIBUTORS BE LIABLE
33  * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
34  * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
35  * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
36  * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
37  * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
38  * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
39  * SUCH DAMAGE.
40  */
41 #undef su_FILE
42 #define su_FILE mime
43 #define mx_SOURCE
44 
45 #ifndef mx_HAVE_AMALGAMATION
46 # include "mx/nail.h"
47 #endif
48 
49 #include <su/cs.h>
50 #include <su/mem.h>
51 #include <su/utf.h>
52 
53 /* TODO nonsense (should be filter chain!) */
54 #include "mx/filter-quote.h"
55 #include "mx/iconv.h"
56 #include "mx/names.h"
57 #include "mx/sigs.h"
58 #include "mx/ui-str.h"
59 
60 /* TODO fake */
61 #include "su/code-in.h"
62 
63 /* Don't ask, but it keeps body and soul together */
64 enum a_mime_structure_hack{
65    a_MIME_SH_NONE,
66    a_MIME_SH_COMMENT,
67    a_MIME_SH_QUOTE
68 };
69 
70 static char                   *_cs_iter_base, *_cs_iter;
71 #ifdef mx_HAVE_ICONV
72 # define _CS_ITER_GET() \
73    ((_cs_iter != NULL) ? _cs_iter : ok_vlook(CHARSET_8BIT_OKEY))
74 #else
75 # define _CS_ITER_GET() ((_cs_iter != NULL) ? _cs_iter : ok_vlook(ttycharset))
76 #endif
77 #define _CS_ITER_STEP() _cs_iter = su_cs_sep_c(&_cs_iter_base, ',', TRU1)
78 
79 /* Is 7-bit enough? */
80 #ifdef mx_HAVE_ICONV
81 static boole           _has_highbit(char const *s);
82 static boole           _name_highbit(struct mx_name *np);
83 #endif
84 
85 /* fwrite(3) while checking for displayability */
86 static sz          _fwrite_td(struct str const *input, enum tdflags flags,
87                            struct str *outrest, struct quoteflt *qf);
88 
89 /* Convert header fields to RFC 2047 format and write to the file fo */
90 static sz          mime_write_tohdr(struct str *in, FILE *fo,
91                            uz *colp, enum a_mime_structure_hack msh);
92 
93 #ifdef mx_HAVE_ICONV
94 static sz a_mime__convhdra(struct str *inp, FILE *fp, uz *colp,
95                   enum a_mime_structure_hack msh);
96 #else
97 # define a_mime__convhdra(S,F,C,MSH) mime_write_tohdr(S, F, C, MSH)
98 #endif
99 
100 /* Write an address to a header field */
101 static sz          mime_write_tohdr_a(struct str *in, FILE *f,
102                            uz *colp, enum a_mime_structure_hack msh);
103 
104 /* Append to buf, handling resizing */
105 static void             _append_str(char **buf, uz *size, uz *pos,
106                            char const *str, uz len);
107 static void             _append_conv(char **buf, uz *size, uz *pos,
108                            char const *str, uz len);
109 
110 #ifdef mx_HAVE_ICONV
111 static boole
_has_highbit(char const * s)112 _has_highbit(char const *s)
113 {
114    boole rv = TRU1;
115    NYD_IN;
116 
117    if (s) {
118       do
119          if ((u8)*s & 0x80)
120             goto jleave;
121       while (*s++ != '\0');
122    }
123    rv = FAL0;
124 jleave:
125    NYD_OU;
126    return rv;
127 }
128 
129 static boole
_name_highbit(struct mx_name * np)130 _name_highbit(struct mx_name *np)
131 {
132    boole rv = TRU1;
133    NYD_IN;
134 
135    while (np) {
136       if (_has_highbit(np->n_name) || _has_highbit(np->n_fullname))
137          goto jleave;
138       np = np->n_flink;
139    }
140    rv = FAL0;
141 jleave:
142    NYD_OU;
143    return rv;
144 }
145 #endif /* mx_HAVE_ICONV */
146 
147 static sigjmp_buf       __mimefwtd_actjmp; /* TODO someday.. */
148 static int              __mimefwtd_sig; /* TODO someday.. */
149 static n_sighdl_t  __mimefwtd_opipe;
150 static void
__mimefwtd_onsig(int sig)151 __mimefwtd_onsig(int sig) /* TODO someday, we won't need it no more */
152 {
153    NYD; /* Signal handler */
154    __mimefwtd_sig = sig;
155    siglongjmp(__mimefwtd_actjmp, 1);
156 }
157 
158 static sz
_fwrite_td(struct str const * input,enum tdflags flags,struct str * outrest,struct quoteflt * qf)159 _fwrite_td(struct str const *input, enum tdflags flags,
160    struct str *outrest, struct quoteflt *qf)
161 {
162    /* TODO note: after send/MIME layer rewrite we will have a string pool
163     * TODO so that memory allocation count drops down massively; for now,
164     * TODO v14.* that is, we pay a lot & heavily depend on the allocator */
165    /* TODO well if we get a broken pipe here, and it happens to
166     * TODO happen pretty easy when sleeping in a full pipe buffer,
167     * TODO then the current codebase performs longjump away;
168     * TODO this leaves memory leaks behind ('think up to 3 per,
169     * TODO dep. upon alloca availability).  For this to be fixed
170     * TODO we either need to get rid of the longjmp()s (tm) or
171     * TODO the storage must come from the outside or be tracked
172     * TODO in a carrier struct.  Best both.  But storage reuse
173     * TODO would be a bigbig win besides */
174    /* *input* _may_ point to non-modifyable buffer; but even then it only
175     * needs to be dup'ed away if we have to transform the content */
176    struct str in, out;
177    sz rv;
178    NYD_IN;
179    UNUSED(outrest);
180 
181    in = *input;
182    out.s = NULL;
183    out.l = 0;
184 
185 #ifdef mx_HAVE_ICONV
186    if ((flags & TD_ICONV) && iconvd != (iconv_t)-1) {
187       int err;
188       char *buf;
189 
190       buf = NULL;
191 
192       if (outrest != NULL && outrest->l > 0) {
193          in.l = outrest->l + input->l;
194          in.s = buf = n_alloc(in.l +1);
195          su_mem_copy(in.s, outrest->s, outrest->l);
196          su_mem_copy(&in.s[outrest->l], input->s, input->l);
197          outrest->l = 0;
198       }
199 
200       rv = 0;
201 
202       /* TODO Sigh, no problem if we have a filter that has a buffer (or
203        * TODO become fed with entire lines, whatever), but for now we need
204        * TODO to ensure we pass entire lines from in here to iconv(3), because
205        * TODO the Citrus iconv(3) will fail tests with stateful encodings
206        * TODO if we do not (only seen on FreeBSD) */
207 #if 0 /* TODO actually not needed indeed, it was known iswprint() error! */
208       if(!(flags & _TD_EOF) && outrest != NULL){
209          uz i, j;
210          char const *cp;
211 
212          if((cp = su_mem_find(in.s, '\n', j = in.l)) != NULL){
213             i = P2UZ(cp - in.s);
214             j -= i;
215             while(j > 0 && *cp == '\n') /* XXX one iteration too much */
216                ++cp, --j, ++i;
217             if(j != 0)
218                n_str_assign_buf(outrest, cp, j);
219             in.l = i;
220          }else{
221             n_str_assign(outrest, &in);
222             goto jleave;
223          }
224       }
225 #endif
226 
227       if((err = n_iconv_str(iconvd, n_ICONV_UNIDEFAULT,
228             &out, &in, &in)) != 0){
229          if(err != su_ERR_INVAL)
230             n_iconv_reset(iconvd);
231 
232          if(outrest != NULL && in.l > 0){
233             /* Incomplete multibyte at EOF is special xxx _INVAL? */
234             if (flags & _TD_EOF) {
235                out.s = n_realloc(out.s, out.l + sizeof(su_utf8_replacer));
236                if(n_psonce & n_PSO_UNICODE){
237                   su_mem_copy(&out.s[out.l], su_utf8_replacer,
238                      sizeof(su_utf8_replacer) -1);
239                   out.l += sizeof(su_utf8_replacer) -1;
240                }else
241                   out.s[out.l++] = '?';
242             } else
243                n_str_add(outrest, &in);
244          }else
245             rv = -1;
246       }
247       in = out;
248       out.l = 0;
249       out.s = NULL;
250       flags &= ~_TD_BUFCOPY;
251 
252       if(buf != NULL)
253          n_free(buf);
254       if(rv < 0)
255          goto jleave;
256    }else
257 #endif /* mx_HAVE_ICONV */
258    /* Else, if we will modify the data bytes and thus introduce the potential
259     * of messing up multibyte sequences which become split over buffer
260     * boundaries TODO and unless we don't have our filter chain which will
261     * TODO make these hacks go by, buffer data until we see a NL */
262          if((flags & (TD_ISPR | TD_DELCTRL)) && outrest != NULL &&
263 #ifdef mx_HAVE_ICONV
264          iconvd == (iconv_t)-1 &&
265 #endif
266          (!(flags & _TD_EOF) || outrest->l > 0)
267    ) {
268       uz i;
269       char *cp;
270 
271       for (cp = &in.s[in.l]; cp > in.s && cp[-1] != '\n'; --cp)
272          ;
273       i = P2UZ(cp - in.s);
274 
275       if (i != in.l) {
276          if (i > 0) {
277             n_str_assign_buf(outrest, cp, in.l - i);
278             cp = n_alloc(i +1);
279             su_mem_copy(cp, in.s, in.l = i);
280             (in.s = cp)[in.l = i] = '\0';
281             flags &= ~_TD_BUFCOPY;
282          } else {
283             n_str_add_buf(outrest, input->s, input->l);
284             rv = 0;
285             goto jleave;
286          }
287       }
288    }
289 
290    if (flags & TD_ISPR)
291       makeprint(&in, &out);
292    else if (flags & _TD_BUFCOPY)
293       n_str_dup(&out, &in);
294    else
295       out = in;
296    if (flags & TD_DELCTRL)
297       out.l = delctrl(out.s, out.l);
298 
299    __mimefwtd_sig = 0;
300    __mimefwtd_opipe = safe_signal(SIGPIPE, &__mimefwtd_onsig);
301    if (sigsetjmp(__mimefwtd_actjmp, 1)) {
302       rv = 0;
303       goto j__sig;
304    }
305 
306    rv = quoteflt_push(qf, out.s, out.l);
307 
308 j__sig:
309    if (out.s != in.s)
310       n_free(out.s);
311    if (in.s != input->s)
312       n_free(in.s);
313    safe_signal(SIGPIPE, __mimefwtd_opipe);
314    if (__mimefwtd_sig != 0)
315       n_raise(__mimefwtd_sig);
316 jleave:
317    NYD_OU;
318    return rv;
319 }
320 
321 static sz
mime_write_tohdr(struct str * in,FILE * fo,uz * colp,enum a_mime_structure_hack msh)322 mime_write_tohdr(struct str *in, FILE *fo, uz *colp,
323    enum a_mime_structure_hack msh)
324 {
325    /* TODO mime_write_tohdr(): we don't know the name of our header->maxcol..
326     * TODO  MIME/send layer rewrite: more available state!!
327     * TODO   Because of this we cannot make a difference in between structured
328     * TODO   and unstructured headers (RFC 2047, 5. (2))
329     * TODO   This means, e.g., that this gets called multiple times for a
330     * TODO   structured header and always starts thinking it is at column 0.
331     * TODO   I.e., it may get called for only the content of a comment etc.,
332     * TODO   not knowing anything of its context.
333     * TODO   Instead we should have a list of header body content tokens,
334     * TODO   convert them, and then dump the converted tokens, breaking lines.
335     * TODO   I.e., get rid of convhdra, mime_write_tohdr_a and such...
336     * TODO   Somewhen, the following should produce smooth stuff:
337     * TODO   '  "Hallo\"," Dr. Backe "Bl\"ö\"d" (Gell) <ha@llöch.en>
338     * TODO    "Nochm\"a\"l"<ta@tu.da>(Dümm)'
339     * TODO NOT MULTIBYTE SAFE IF AN ENCODED WORD HAS TO BE SPLIT!
340     * TODO  To be better we had to mbtowc_l() (non-std! and no locale!!) and
341     * TODO   work char-wise!  ->  S-CText..
342     * TODO  The real problem for STD compatibility is however that "in" is
343     * TODO   already iconv(3) encoded to the target character set!  We could
344     * TODO   also solve it (very expensively!) if we would narrow down to an
345     * TODO   encoded word and then iconv(3)+MIME encode in one go, in which
346     * TODO   case multibyte errors could be caught! */
347    enum {
348       /* Maximum line length */
349       a_MAXCOL_NENC = MIME_LINELEN,
350       a_MAXCOL = MIME_LINELEN_RFC2047
351    };
352 
353    struct str cout, cin;
354    enum {
355       _FIRST      = 1<<0,  /* Nothing written yet, start of string */
356       _MSH_NOTHING = 1<<1, /* Now, really: nothing at all has been written */
357       a_ANYENC = 1<<2,     /* We have RFC 2047 anything at least once */
358       _NO_QP      = 1<<3,  /* No quoted-printable allowed */
359       _NO_B64     = 1<<4,  /* Ditto, base64 */
360       _ENC_LAST   = 1<<5,  /* Last round generated encoded word */
361       _SHOULD_BEE = 1<<6,  /* Avoid lines longer than SHOULD via encoding */
362       _RND_SHIFT  = 7,
363       _RND_MASK   = (1<<_RND_SHIFT) - 1,
364       _SPACE      = 1<<(_RND_SHIFT+1),    /* Leading whitespace */
365       _8BIT       = 1<<(_RND_SHIFT+2),    /* High bit set */
366       _ENCODE     = 1<<(_RND_SHIFT+3),    /* Need encoding */
367       _ENC_B64    = 1<<(_RND_SHIFT+4),    /* - let it be base64 */
368       _OVERLONG   = 1<<(_RND_SHIFT+5)     /* Temporarily raised limit */
369    } flags;
370    char const *cset7, *cset8, *wbot, *upper, *wend, *wcur;
371    u32 cset7_len, cset8_len;
372    uz col, i, j;
373    sz size;
374 
375    NYD_IN;
376 
377    cout.s = NULL, cout.l = 0;
378    cset7 = ok_vlook(charset_7bit);
379    cset7_len = (u32)su_cs_len(cset7);
380    cset8 = _CS_ITER_GET(); /* TODO MIME/send layer: iter active? iter! else */
381    cset8_len = (u32)su_cs_len(cset8);
382 
383    flags = _FIRST;
384    if(msh != a_MIME_SH_NONE)
385       flags |= _MSH_NOTHING;
386 
387    /* RFC 1468, "MIME Considerations":
388     *     ISO-2022-JP may also be used in MIME Part 2 headers.  The "B"
389     *     encoding should be used with ISO-2022-JP text. */
390    /* TODO of course, our current implementation won't deal properly with
391     * TODO any stateful encoding at all... (the standard says each encoded
392     * TODO word must include all necessary reset sequences..., i.e., each
393     * TODO encoded word must be a self-contained iconv(3) life cycle) */
394    if (!su_cs_cmp_case(cset8, "iso-2022-jp") || mime_enc_target() == MIMEE_B64)
395       flags |= _NO_QP;
396 
397    wbot = in->s;
398    upper = wbot + in->l;
399    size = 0;
400 
401    if(colp == NULL || (col = *colp) == 0)
402       col = sizeof("Mail-Followup-To: ") -1; /* TODO dreadful thing */
403 
404    /* The user may specify empty quoted-strings or comments, keep them! */
405    if(wbot == upper) {
406       if(flags & _MSH_NOTHING){
407          flags &= ~_MSH_NOTHING;
408          putc((msh == a_MIME_SH_COMMENT ? '(' : '"'), fo);
409          size = 1;
410          ++col;
411       }
412    } else for (; wbot < upper; flags &= ~_FIRST, wbot = wend) {
413       flags &= _RND_MASK;
414       wcur = wbot;
415       while (wcur < upper && su_cs_is_white(*wcur)) {
416          flags |= _SPACE;
417          ++wcur;
418       }
419 
420       /* Any occurrence of whitespace resets prevention of lines >SHOULD via
421        * enforced encoding (xxx SHOULD, but.. encoding is expensive!!) */
422       if (flags & _SPACE)
423          flags &= ~_SHOULD_BEE;
424 
425      /* Data ends with WS - dump it and done.
426       * Also, if we have seen multiple successive whitespace characters, then
427       * if there was no encoded word last, i.e., if we can simply take them
428       * over to the output as-is, keep one WS for possible later separation
429       * purposes and simply print the others as-is, directly! */
430       if (wcur == upper) {
431          wend = wcur;
432          goto jnoenc_putws;
433       }
434       if ((flags & (_ENC_LAST | _SPACE)) == _SPACE && wcur - wbot > 1) {
435          wend = wcur - 1;
436          goto jnoenc_putws;
437       }
438 
439       /* Skip over a word to next non-whitespace, keep track along the way
440        * whether our 7-bit charset suffices to represent the data */
441       for (wend = wcur; wend < upper; ++wend) {
442          if (su_cs_is_white(*wend))
443             break;
444          if ((uc)*wend & 0x80)
445             flags |= _8BIT;
446       }
447 
448       /* Decide whether the range has to become encoded or not */
449       i = P2UZ(wend - wcur);
450       j = mime_enc_mustquote(wcur, i, MIMEEF_ISHEAD);
451       /* If it just cannot fit on a SHOULD line length, force encode */
452       if (i > a_MAXCOL_NENC) {
453          flags |= _SHOULD_BEE; /* (Sigh: SHOULD only, not MUST..) */
454          goto j_beejump;
455       }
456       if ((flags & _SHOULD_BEE) || j > 0) {
457 j_beejump:
458          flags |= _ENCODE;
459          /* Use base64 if requested or more than 50% -37.5-% of the bytes of
460           * the string need to be encoded */
461          if ((flags & _NO_QP) || j >= i >> 1)/*(i >> 2) + (i >> 3))*/
462             flags |= _ENC_B64;
463       }
464       su_DBG( if (flags & _8BIT) ASSERT(flags & _ENCODE); )
465 
466       if (!(flags & _ENCODE)) {
467          /* Encoded word produced, but no linear whitespace for necessary RFC
468           * 2047 separation?  Generate artificial data (bad standard!) */
469          if ((flags & (_ENC_LAST | _SPACE)) == _ENC_LAST) {
470             if (col >= a_MAXCOL) {
471                putc('\n', fo);
472                ++size;
473                col = 0;
474             }
475             if(flags & _MSH_NOTHING){
476                flags &= ~_MSH_NOTHING;
477                putc((msh == a_MIME_SH_COMMENT ? '(' : '"'), fo);
478                ++size;
479                ++col;
480             }
481             putc(' ', fo);
482             ++size;
483             ++col;
484          }
485 
486 jnoenc_putws:
487          flags &= ~_ENC_LAST;
488 
489          /* todo No effort here: (1) v15.0 has to bring complete rewrite,
490           * todo (2) the standard is braindead and (3) usually this is one
491           * todo word only, and why be smarter than the standard? */
492 jnoenc_retry:
493          i = P2UZ(wend - wbot);
494          if (i + col + ((flags & _MSH_NOTHING) != 0) <=
495                   (flags & _OVERLONG ? MIME_LINELEN_MAX
496                    : (flags & a_ANYENC ? a_MAXCOL : a_MAXCOL_NENC))) {
497             if(flags & _MSH_NOTHING){
498                flags &= ~_MSH_NOTHING;
499                putc((msh == a_MIME_SH_COMMENT ? '(' : '"'), fo);
500                ++size;
501                ++col;
502             }
503             i = fwrite(wbot, sizeof *wbot, i, fo);
504             size += i;
505             col += i;
506             continue;
507          }
508 
509          /* Doesn't fit, try to break the line first; */
510          if (col > 1) {
511             putc('\n', fo);
512             if (su_cs_is_white(*wbot)) {
513                putc((uc)*wbot, fo);
514                ++wbot;
515             } else
516                putc(' ', fo); /* Bad standard: artificial data! */
517             size += 2;
518             col = 1;
519             if(flags & _MSH_NOTHING){
520                flags &= ~_MSH_NOTHING;
521                putc((msh == a_MIME_SH_COMMENT ? '(' : '"'), fo);
522                ++size;
523                ++col;
524             }
525             flags |= _OVERLONG;
526             goto jnoenc_retry;
527          }
528 
529          /* It is so long that it needs to be broken, effectively causing
530           * artificial spaces to be inserted (bad standard), yuck */
531          /* todo This is not multibyte safe, as above; and completely stupid
532           * todo P.S.: our _SHOULD_BEE prevents these cases in the meanwhile */
533 /* FIXME n_PSO_UNICODE and parse using UTF-8 sync possibility! */
534          wcur = wbot + MIME_LINELEN_MAX - 8;
535          while (wend > wcur)
536             wend -= 4;
537          goto jnoenc_retry;
538       } else {
539          /* Encoding to encoded word(s); deal with leading whitespace, place
540           * a separator first as necessary: encoded words must always be
541           * separated from text and other encoded words with linear WS.
542           * And if an encoded word was last, intermediate whitespace must
543           * also be encoded, otherwise it would get stripped away! */
544          wcur = n_UNCONST(n_empty);
545          if ((flags & (_ENC_LAST | _SPACE)) != _SPACE) {
546             /* Reinclude whitespace */
547             flags &= ~_SPACE;
548             /* We don't need to place a separator at the very beginning */
549             if (!(flags & _FIRST))
550                wcur = n_UNCONST(" ");
551          } else
552             wcur = wbot++;
553 
554          flags |= a_ANYENC | _ENC_LAST;
555          n_pstate |= n_PS_HEADER_NEEDED_MIME;
556 
557          /* RFC 2047:
558           *    An 'encoded-word' may not be more than 75 characters long,
559           *    including 'charset', 'encoding', 'encoded-text', and
560           *    delimiters.  If it is desirable to encode more text than will
561           *    fit in an 'encoded-word' of 75 characters, multiple
562           *    'encoded-word's (separated by CRLF SPACE) may be used.
563           *
564           *    While there is no limit to the length of a multiple-line
565           *    header field, each line of a header field that contains one
566           *    or more 'encoded-word's is limited to 76 characters */
567 jenc_retry:
568          cin.s = n_UNCONST(wbot);
569          cin.l = P2UZ(wend - wbot);
570 
571          /* C99 */{
572             struct str *xout;
573 
574             if(flags & _ENC_B64)
575                xout = b64_encode(&cout, &cin, B64_ISHEAD | B64_ISENCWORD);
576             else
577                xout = qp_encode(&cout, &cin, QP_ISHEAD | QP_ISENCWORD);
578             if(xout == NULL){
579                size = -1;
580                break;
581             }
582             j = xout->l;
583          }
584          /* (Avoid trigraphs in the RFC 2047 placeholder..) */
585          i = j + (flags & _8BIT ? cset8_len : cset7_len) +
586                sizeof("=!!B!!=") -1;
587          if (*wcur != '\0')
588             ++i;
589 
590 jenc_retry_same:
591          /* Unfortunately RFC 2047 explicitly disallows encoded words to be
592           * longer (just like RFC 5322's "a line SHOULD fit in 78 but MAY be
593           * 998 characters long"), so we cannot use the _OVERLONG mechanism,
594           * even though all tested mailers seem to support it */
595          if(i + col <= (/*flags & _OVERLONG ? MIME_LINELEN_MAX :*/ a_MAXCOL)){
596             if(flags & _MSH_NOTHING){
597                flags &= ~_MSH_NOTHING;
598                putc((msh == a_MIME_SH_COMMENT ? '(' : '"'), fo);
599                ++size;
600                ++col;
601             }
602             fprintf(fo, "%.1s=?%s?%c?%.*s?=",
603                wcur, (flags & _8BIT ? cset8 : cset7),
604                (flags & _ENC_B64 ? 'B' : 'Q'),
605                (int)cout.l, cout.s);
606             size += i;
607             col += i;
608             continue;
609          }
610 
611          /* Doesn't fit, try to break the line first */
612          /* TODO I've commented out the _FIRST test since we (1) cannot do
613           * TODO _OVERLONG since (MUAs support but) the standard disallows,
614           * TODO and because of our iconv problem i prefer an empty first line
615           * TODO in favour of a possibly messed up multibytes character. :-( */
616          if (col > 1 /* TODO && !(flags & _FIRST)*/) {
617             putc('\n', fo);
618             size += 2;
619             col = 1;
620             if (!(flags & _SPACE)) {
621                putc(' ', fo);
622                wcur = n_UNCONST(n_empty);
623                /*flags |= _OVERLONG;*/
624                goto jenc_retry_same;
625             } else {
626                putc((uc)*wcur, fo);
627                if (su_cs_is_white(*(wcur = wbot)))
628                   ++wbot;
629                else {
630                   flags &= ~_SPACE;
631                   wcur = n_UNCONST(n_empty);
632                }
633                /*flags &= ~_OVERLONG;*/
634                goto jenc_retry;
635             }
636          }
637 
638          /* It is so long that it needs to be broken, effectively causing
639           * artificial data to be inserted (bad standard), yuck */
640          /* todo This is not multibyte safe, as above */
641          /*if (!(flags & _OVERLONG)) { Mechanism explicitly forbidden by 2047
642             flags |= _OVERLONG;
643             goto jenc_retry;
644          }*/
645 
646 /* FIXME n_PSO_UNICODE and parse using UTF-8 sync possibility! */
647          i = P2UZ(wend - wbot) + !!(flags & _SPACE);
648          j = 3 + !(flags & _ENC_B64);
649          for (;;) {
650             wend -= j;
651             i -= j;
652             /* (Note the problem most likely is the transfer-encoding blow,
653              * which is why we test this *after* the decrements.. */
654             if (i <= a_MAXCOL)
655                break;
656          }
657          goto jenc_retry;
658       }
659    }
660 
661    if(!(flags & _MSH_NOTHING) && msh != a_MIME_SH_NONE){
662       putc((msh == a_MIME_SH_COMMENT ? ')' : '"'), fo);
663       ++size;
664       ++col;
665    }
666 
667    if(cout.s != NULL)
668       n_free(cout.s);
669 
670    if(colp != NULL)
671       *colp = col;
672    NYD_OU;
673    return size;
674 }
675 
676 #ifdef mx_HAVE_ICONV
677 static sz
a_mime__convhdra(struct str * inp,FILE * fp,uz * colp,enum a_mime_structure_hack msh)678 a_mime__convhdra(struct str *inp, FILE *fp, uz *colp,
679       enum a_mime_structure_hack msh){
680    struct str ciconv;
681    sz rv;
682    NYD_IN;
683 
684    rv = 0;
685    ciconv.s = NULL;
686 
687    if(inp->l > 0 && iconvd != (iconv_t)-1){
688       ciconv.l = 0;
689       if(n_iconv_str(iconvd, n_ICONV_NONE, &ciconv, inp, NULL) != 0){
690          n_iconv_reset(iconvd);
691          rv = -1;
692          goto jleave;
693       }
694       *inp = ciconv;
695    }
696 
697    rv = mime_write_tohdr(inp, fp, colp, msh);
698 jleave:
699    if(ciconv.s != NULL)
700       n_free(ciconv.s);
701    NYD_OU;
702    return rv;
703 }
704 #endif /* mx_HAVE_ICONV */
705 
706 static sz
mime_write_tohdr_a(struct str * in,FILE * f,uz * colp,enum a_mime_structure_hack msh)707 mime_write_tohdr_a(struct str *in, FILE *f, uz *colp,
708    enum a_mime_structure_hack msh)
709 {
710    struct str xin;
711    uz i;
712    char const *cp, *lastcp;
713    sz size, x;
714    NYD_IN;
715 
716    in->s[in->l] = '\0';
717 
718    if((cp = routeaddr(lastcp = in->s)) != NULL && cp > lastcp) {
719       xin.s = n_UNCONST(lastcp);
720       xin.l = P2UZ(cp - lastcp);
721       if ((size = a_mime__convhdra(&xin, f, colp, msh)) < 0)
722          goto jleave;
723       lastcp = cp;
724    } else {
725       cp = lastcp;
726       size = 0;
727    }
728 
729    for( ; *cp != '\0'; ++cp){
730       switch(*cp){
731       case '(':
732          i = P2UZ(cp - lastcp);
733          if(i > 0){
734             if(fwrite(lastcp, 1, i, f) != i)
735                goto jerr;
736             size += i;
737          }
738          lastcp = ++cp;
739          cp = skip_comment(cp);
740          if(cp > lastcp)
741             --cp;
742          /* We want to keep empty comments, too! */
743          xin.s = n_UNCONST(lastcp);
744          xin.l = P2UZ(cp - lastcp);
745          if ((x = a_mime__convhdra(&xin, f, colp, a_MIME_SH_COMMENT)) < 0)
746             goto jerr;
747          size += x;
748          lastcp = &cp[1];
749          break;
750       case '"':
751          i = P2UZ(cp - lastcp);
752          if(i > 0){
753             if(fwrite(lastcp, 1, i, f) != i)
754                goto jerr;
755             size += i;
756          }
757          for(lastcp = ++cp; *cp != '\0'; ++cp){
758             if(*cp == '"')
759                break;
760             if(*cp == '\\' && cp[1] != '\0')
761                ++cp;
762          }
763          /* We want to keep empty quoted-strings, too! */
764          xin.s = n_UNCONST(lastcp);
765          xin.l = P2UZ(cp - lastcp);
766          if((x = a_mime__convhdra(&xin, f, colp, a_MIME_SH_QUOTE)) < 0)
767             goto jerr;
768          size += x;
769          ++size;
770          lastcp = &cp[1];
771          break;
772       }
773    }
774 
775    i = P2UZ(cp - lastcp);
776    if(i > 0){
777       if(fwrite(lastcp, 1, i, f) != i)
778          goto jerr;
779       size += i;
780    }
781 jleave:
782    NYD_OU;
783    return size;
784 jerr:
785    size = -1;
786    goto jleave;
787 }
788 
789 static void
_append_str(char ** buf,uz * size,uz * pos,char const * str,uz len)790 _append_str(char **buf, uz *size, uz *pos, char const *str, uz len)
791 {
792    NYD_IN;
793    *buf = n_realloc(*buf, *size += len);
794    su_mem_copy(&(*buf)[*pos], str, len);
795    *pos += len;
796    NYD_OU;
797 }
798 
799 static void
_append_conv(char ** buf,uz * size,uz * pos,char const * str,uz len)800 _append_conv(char **buf, uz *size, uz *pos, char const *str, uz len)
801 {
802    struct str in, out;
803    NYD_IN;
804 
805    in.s = n_UNCONST(str);
806    in.l = len;
807    mime_fromhdr(&in, &out, TD_ISPR | TD_ICONV);
808    _append_str(buf, size, pos, out.s, out.l);
809    n_free(out.s);
810    NYD_OU;
811 }
812 
813 FL boole
charset_iter_reset(char const * a_charset_to_try_first)814 charset_iter_reset(char const *a_charset_to_try_first) /* TODO elim. dups! */
815 {
816    char const *sarr[3];
817    uz sarrl[3], len;
818    char *cp;
819    NYD_IN;
820    UNUSED(a_charset_to_try_first);
821 
822 #ifdef mx_HAVE_ICONV
823    sarr[2] = ok_vlook(CHARSET_8BIT_OKEY);
824 
825    if(a_charset_to_try_first != NULL &&
826          su_cs_cmp(a_charset_to_try_first, sarr[2]))
827       sarr[0] = a_charset_to_try_first;
828    else
829       sarr[0] = NULL;
830 
831    if((sarr[1] = ok_vlook(sendcharsets)) == NULL &&
832          ok_blook(sendcharsets_else_ttycharset)){
833       cp = n_UNCONST(ok_vlook(ttycharset));
834       if(su_cs_cmp(cp, sarr[2]) && (sarr[0] == NULL || su_cs_cmp(cp, sarr[0])))
835          sarr[1] = cp;
836    }
837 #else
838    sarr[2] = ok_vlook(ttycharset);
839 #endif
840 
841    sarrl[2] = len = su_cs_len(sarr[2]);
842 #ifdef mx_HAVE_ICONV
843    if ((cp = n_UNCONST(sarr[1])) != NULL)
844       len += (sarrl[1] = su_cs_len(cp));
845    else
846       sarrl[1] = 0;
847    if ((cp = n_UNCONST(sarr[0])) != NULL)
848       len += (sarrl[0] = su_cs_len(cp));
849    else
850       sarrl[0] = 0;
851 #endif
852 
853    _cs_iter_base = cp = n_autorec_alloc(len + 1 + 1 +1);
854 
855 #ifdef mx_HAVE_ICONV
856    if ((len = sarrl[0]) != 0) {
857       su_mem_copy(cp, sarr[0], len);
858       cp[len] = ',';
859       cp += ++len;
860    }
861    if ((len = sarrl[1]) != 0) {
862       su_mem_copy(cp, sarr[1], len);
863       cp[len] = ',';
864       cp += ++len;
865    }
866 #endif
867    len = sarrl[2];
868    su_mem_copy(cp, sarr[2], len);
869    cp[len] = '\0';
870 
871    _CS_ITER_STEP();
872    NYD_OU;
873    return (_cs_iter != NULL);
874 }
875 
876 FL boole
charset_iter_next(void)877 charset_iter_next(void)
878 {
879    boole rv;
880    NYD_IN;
881 
882    _CS_ITER_STEP();
883    rv = (_cs_iter != NULL);
884    NYD_OU;
885    return rv;
886 }
887 
888 FL boole
charset_iter_is_valid(void)889 charset_iter_is_valid(void)
890 {
891    boole rv;
892    NYD_IN;
893 
894    rv = (_cs_iter != NULL);
895    NYD_OU;
896    return rv;
897 }
898 
899 FL char const *
charset_iter(void)900 charset_iter(void)
901 {
902    char const *rv;
903    NYD_IN;
904 
905    rv = _cs_iter;
906    NYD_OU;
907    return rv;
908 }
909 
910 FL char const *
charset_iter_or_fallback(void)911 charset_iter_or_fallback(void)
912 {
913    char const *rv;
914    NYD_IN;
915 
916    rv = _CS_ITER_GET();
917    NYD_OU;
918    return rv;
919 }
920 
921 FL void
charset_iter_recurse(char * outer_storage[2])922 charset_iter_recurse(char *outer_storage[2]) /* TODO LEGACY FUN, REMOVE */
923 {
924    NYD_IN;
925    outer_storage[0] = _cs_iter_base;
926    outer_storage[1] = _cs_iter;
927    NYD_OU;
928 }
929 
930 FL void
charset_iter_restore(char * outer_storage[2])931 charset_iter_restore(char *outer_storage[2]) /* TODO LEGACY FUN, REMOVE */
932 {
933    NYD_IN;
934    _cs_iter_base = outer_storage[0];
935    _cs_iter = outer_storage[1];
936    NYD_OU;
937 }
938 
939 #ifdef mx_HAVE_ICONV
940 FL char const *
need_hdrconv(struct header * hp)941 need_hdrconv(struct header *hp) /* TODO once only, then iter */
942 {
943    struct n_header_field *hfp;
944    char const *rv;
945    NYD_IN;
946 
947    rv = NULL;
948 
949    /* C99 */{
950       struct n_header_field *chlp[3]; /* TODO JOINED AFTER COMPOSE! */
951       u32 i;
952 
953       chlp[0] = n_poption_arg_C;
954       chlp[1] = n_customhdr_list;
955       chlp[2] = hp->h_user_headers;
956 
957       for(i = 0; i < NELEM(chlp); ++i)
958          if((hfp = chlp[i]) != NULL)
959             do if(_has_highbit(hfp->hf_dat + hfp->hf_nl +1))
960                goto jneeds;
961             while((hfp = hfp->hf_next) != NULL);
962    }
963 
964    if (hp->h_mft != NULL) {
965       if (_name_highbit(hp->h_mft))
966          goto jneeds;
967    }
968    if (hp->h_from != NULL) {
969       if (_name_highbit(hp->h_from))
970          goto jneeds;
971    } else if (_has_highbit(myaddrs(NULL)))
972       goto jneeds;
973    if (hp->h_reply_to) {
974       if (_name_highbit(hp->h_reply_to))
975          goto jneeds;
976    } else {
977       char const *v15compat;
978 
979       if((v15compat = ok_vlook(replyto)) != NULL)
980          n_OBSOLETE(_("please use *reply-to*, not *replyto*"));
981       if(_has_highbit(v15compat))
982          goto jneeds;
983       if(_has_highbit(ok_vlook(reply_to)))
984          goto jneeds;
985    }
986    if (hp->h_sender) {
987       if (_name_highbit(hp->h_sender))
988          goto jneeds;
989    } else if (_has_highbit(ok_vlook(sender)))
990       goto jneeds;
991 
992    if (_name_highbit(hp->h_to))
993       goto jneeds;
994    if (_name_highbit(hp->h_cc))
995       goto jneeds;
996    if (_name_highbit(hp->h_bcc))
997       goto jneeds;
998    if (_has_highbit(hp->h_subject))
999 jneeds:
1000       rv = _CS_ITER_GET(); /* TODO MIME/send: iter active? iter! else */
1001    NYD_OU;
1002    return rv;
1003 }
1004 #endif /* mx_HAVE_ICONV */
1005 
1006 FL void
mime_fromhdr(struct str const * in,struct str * out,enum tdflags flags)1007 mime_fromhdr(struct str const *in, struct str *out, enum tdflags flags)
1008 {
1009    /* TODO mime_fromhdr(): is called with strings that contain newlines;
1010     * TODO this is the usual newline problem all around the codebase;
1011     * TODO i.e., if we strip it, then the display misses it ;>
1012     * TODO this is why it is so messy and why S-nail v14.2 plus additional
1013     * TODO patch for v14.5.2 (and maybe even v14.5.3 subminor) occurred, and
1014     * TODO why our display reflects what is contained in the message: the 1:1
1015     * TODO relationship of message content and display!
1016     * TODO instead a header line should be decoded to what it is (a single
1017     * TODO line that is) and it should be objective to the backend whether
1018     * TODO it'll be folded to fit onto the display or not, e.g., for search
1019     * TODO purposes etc.  then the only condition we have to honour in here
1020     * TODO is that whitespace in between multiple adjacent MIME encoded words
1021     * TODO á la RFC 2047 is discarded; i.e.: this function should deal with
1022     * TODO RFC 2047 and be renamed: mime_fromhdr() -> mime_rfc2047_decode() */
1023    struct str cin, cout;
1024    char *p, *op, *upper;
1025    u32 convert, lastenc, lastoutl;
1026 #ifdef mx_HAVE_ICONV
1027    char const *tcs;
1028    char *cbeg;
1029    iconv_t fhicd = (iconv_t)-1;
1030 #endif
1031    NYD_IN;
1032 
1033    out->l = 0;
1034    if (in->l == 0) {
1035       *(out->s = n_alloc(1)) = '\0';
1036       goto jleave;
1037    }
1038    out->s = NULL;
1039 
1040 #ifdef mx_HAVE_ICONV
1041    tcs = ok_vlook(ttycharset);
1042 #endif
1043    p = in->s;
1044    upper = p + in->l;
1045    lastenc = lastoutl = 0;
1046 
1047    while (p < upper) {
1048       op = p;
1049       if (*p == '=' && *(p + 1) == '?') {
1050          p += 2;
1051 #ifdef mx_HAVE_ICONV
1052          cbeg = p;
1053 #endif
1054          while (p < upper && *p != '?')
1055             ++p;  /* strip charset */
1056          if (p >= upper)
1057             goto jnotmime;
1058          ++p;
1059 #ifdef mx_HAVE_ICONV
1060          if (flags & TD_ICONV) {
1061             uz i = P2UZ(p - cbeg);
1062             char *ltag, *cs = n_lofi_alloc(i);
1063 
1064             su_mem_copy(cs, cbeg, --i);
1065             cs[i] = '\0';
1066             /* RFC 2231 extends the RFC 2047 character set definition in
1067              * encoded words by language tags - silently strip those off */
1068             if ((ltag = su_cs_find_c(cs, '*')) != NULL)
1069                *ltag = '\0';
1070 
1071             if (fhicd != (iconv_t)-1)
1072                n_iconv_close(fhicd);
1073             fhicd = su_cs_cmp_case(cs, tcs)
1074                   ? n_iconv_open(tcs, cs) : (iconv_t)-1;
1075             n_lofi_free(cs);
1076          }
1077 #endif
1078          switch (*p) {
1079          case 'B': case 'b':
1080             convert = CONV_FROMB64;
1081             break;
1082          case 'Q': case 'q':
1083             convert = CONV_FROMQP;
1084             break;
1085          default: /* invalid, ignore */
1086             goto jnotmime;
1087          }
1088          if (*++p != '?')
1089             goto jnotmime;
1090          cin.s = ++p;
1091          cin.l = 1;
1092          for (;;) {
1093             if (PCMP(p + 1, >=, upper))
1094                goto jnotmime;
1095             if (*p++ == '?' && *p == '=')
1096                break;
1097             ++cin.l;
1098          }
1099          ++p;
1100          --cin.l;
1101 
1102          cout.s = NULL;
1103          cout.l = 0;
1104          if (convert == CONV_FROMB64) {
1105             if(!b64_decode_header(&cout, &cin))
1106                n_str_assign_cp(&cout, _("[Invalid Base64 encoding]"));
1107          }else if(!qp_decode_header(&cout, &cin))
1108             n_str_assign_cp(&cout, _("[Invalid Quoted-Printable encoding]"));
1109          /* Normalize all decoded newlines to spaces XXX only \0/\n yet */
1110          /* C99 */{
1111             char const *xcp;
1112             boole any;
1113             uz i, j;
1114 
1115             for(any = FAL0, i = cout.l; i-- != 0;)
1116                switch(cout.s[i]){
1117                case '\0':
1118                case '\n':
1119                   any = TRU1;
1120                   cout.s[i] = ' ';
1121                   /* FALLTHRU */
1122                default:
1123                   break;
1124 
1125                }
1126 
1127             if(any){
1128                /* I18N: must be non-empty, last must be closing bracket/xy */
1129                xcp = _("[Content normalized: ]");
1130                i = su_cs_len(xcp);
1131                j = cout.l;
1132                n_str_add_buf(&cout, xcp, i);
1133                su_mem_move(&cout.s[i - 1], cout.s, j);
1134                su_mem_copy(&cout.s[0], xcp, i - 1);
1135                cout.s[cout.l - 1] = xcp[i - 1];
1136             }
1137          }
1138 
1139 
1140          out->l = lastenc;
1141 #ifdef mx_HAVE_ICONV
1142          /* TODO Does not really work if we have assigned some ASCII or even
1143           * TODO translated strings because of errors! */
1144          if ((flags & TD_ICONV) && fhicd != (iconv_t)-1) {
1145             cin.s = NULL, cin.l = 0; /* XXX string pool ! */
1146             convert = n_iconv_str(fhicd, n_ICONV_UNIDEFAULT, &cin, &cout, NIL);
1147             out = n_str_add(out, &cin);
1148             if (convert) {/* su_ERR_INVAL at EOS */
1149                n_iconv_reset(fhicd);
1150                out = n_str_add_buf(out, n_qm, 1);/* TODO unicode replacement */
1151             }
1152             n_free(cin.s);
1153          } else
1154 #endif
1155             out = n_str_add(out, &cout);
1156          lastenc = lastoutl = out->l;
1157          n_free(cout.s);
1158       } else
1159 jnotmime: {
1160          boole onlyws;
1161 
1162          p = op;
1163          onlyws = (lastenc > 0);
1164          for (;;) {
1165             if (++op == upper)
1166                break;
1167             if (op[0] == '=' && (PCMP(op + 1, ==, upper) || op[1] == '?'))
1168                break;
1169             if (onlyws && !su_cs_is_blank(*op))
1170                onlyws = FAL0;
1171          }
1172 
1173          out = n_str_add_buf(out, p, P2UZ(op - p));
1174          p = op;
1175          if (!onlyws || lastoutl != lastenc)
1176             lastenc = out->l;
1177          lastoutl = out->l;
1178       }
1179    }
1180    out->s[out->l] = '\0';
1181 
1182    if (flags & TD_ISPR) {
1183       makeprint(out, &cout);
1184       n_free(out->s);
1185       *out = cout;
1186    }
1187    if (flags & TD_DELCTRL)
1188       out->l = delctrl(out->s, out->l);
1189 #ifdef mx_HAVE_ICONV
1190    if (fhicd != (iconv_t)-1)
1191       n_iconv_close(fhicd);
1192 #endif
1193 jleave:
1194    NYD_OU;
1195    return;
1196 }
1197 
1198 FL char *
mime_fromaddr(char const * name)1199 mime_fromaddr(char const *name)
1200 {
1201    char const *cp, *lastcp;
1202    char *res = NULL;
1203    uz ressz = 1, rescur = 0;
1204    NYD_IN;
1205 
1206    if (name == NULL)
1207       goto jleave;
1208    if (*name == '\0') {
1209       res = savestr(name);
1210       goto jleave;
1211    }
1212 
1213    if ((cp = routeaddr(name)) != NULL && cp > name) {
1214       _append_conv(&res, &ressz, &rescur, name, P2UZ(cp - name));
1215       lastcp = cp;
1216    } else
1217       cp = lastcp = name;
1218 
1219    for ( ; *cp; ++cp) {
1220       switch (*cp) {
1221       case '(':
1222          _append_str(&res, &ressz, &rescur, lastcp, P2UZ(cp - lastcp + 1));
1223          lastcp = ++cp;
1224          cp = skip_comment(cp);
1225          if (--cp > lastcp)
1226             _append_conv(&res, &ressz, &rescur, lastcp, P2UZ(cp - lastcp));
1227          lastcp = cp;
1228          break;
1229       case '"':
1230          while (*cp) {
1231             if (*++cp == '"')
1232                break;
1233             if (*cp == '\\' && cp[1] != '\0')
1234                ++cp;
1235          }
1236          break;
1237       }
1238    }
1239    if (cp > lastcp)
1240       _append_str(&res, &ressz, &rescur, lastcp, P2UZ(cp - lastcp));
1241    /* C99 */{
1242       char *x;
1243 
1244       x = res;
1245       res = savestrbuf(res, rescur);
1246       if(x != NULL)
1247          n_free(x);
1248    }
1249 jleave:
1250    NYD_OU;
1251    return res;
1252 }
1253 
1254 FL sz
xmime_write(char const * ptr,uz size,FILE * f,enum conversion convert,enum tdflags dflags,struct str * volatile outrest,struct str * volatile inrest)1255 xmime_write(char const *ptr, uz size, FILE *f, enum conversion convert,
1256    enum tdflags dflags, struct str * volatile outrest,
1257    struct str * volatile inrest)
1258 {
1259    sz rv;
1260    struct quoteflt *qf;
1261    NYD_IN;
1262 
1263    quoteflt_reset(qf = quoteflt_dummy(), f);
1264    rv = mime_write(ptr, size, f, convert, dflags, qf, outrest, inrest);
1265    quoteflt_flush(qf);
1266    NYD_OU;
1267    return rv;
1268 }
1269 
1270 static sigjmp_buf       __mimemw_actjmp; /* TODO someday.. */
1271 static int              __mimemw_sig; /* TODO someday.. */
1272 static n_sighdl_t  __mimemw_opipe;
1273 static void
__mimemw_onsig(int sig)1274 __mimemw_onsig(int sig) /* TODO someday, we won't need it no more */
1275 {
1276    NYD; /* Signal handler */
1277    __mimemw_sig = sig;
1278    siglongjmp(__mimemw_actjmp, 1);
1279 }
1280 
1281 FL sz
mime_write(char const * ptr,uz size,FILE * f,enum conversion convert,enum tdflags volatile dflags,struct quoteflt * qf,struct str * volatile outrest,struct str * volatile inrest)1282 mime_write(char const *ptr, uz size, FILE *f,
1283    enum conversion convert, enum tdflags volatile dflags,
1284    struct quoteflt *qf, struct str * volatile outrest,
1285    struct str * volatile inrest)
1286 {
1287    /* TODO note: after send/MIME layer rewrite we will have a string pool
1288     * TODO so that memory allocation count drops down massively; for now,
1289     * TODO v14.0 that is, we pay a lot & heavily depend on the allocator.
1290     * TODO P.S.: furthermore all this encapsulated in filter objects instead */
1291    struct str in, out;
1292    sz volatile xsize;
1293    NYD_IN;
1294 
1295    dflags |= _TD_BUFCOPY;
1296    in.s = n_UNCONST(ptr);
1297    in.l = size;
1298    out.s = NULL;
1299    out.l = 0;
1300 
1301    if((xsize = size) == 0){
1302       if(inrest != NULL && inrest->l != 0)
1303          goto jinrest;
1304       if(outrest != NULL && outrest->l != 0)
1305          goto jconvert;
1306       goto jleave;
1307    }
1308 
1309    /* TODO This crap requires linewise input, then.  We need a filter chain
1310     * TODO as in input->iconv->base64 where each filter can have its own
1311     * TODO buffer, with a filter->fflush() call to get rid of those! */
1312 #ifdef mx_HAVE_ICONV
1313    if ((dflags & TD_ICONV) && iconvd != (iconv_t)-1 &&
1314          (convert == CONV_TOQP || convert == CONV_8BIT ||
1315          convert == CONV_TOB64 || convert == CONV_TOHDR)) {
1316       if (n_iconv_str(iconvd, n_ICONV_NONE, &out, &in, NULL) != 0) {
1317          n_iconv_reset(iconvd);
1318          /* TODO This causes hard-failure.  We would need to have an action
1319           * TODO policy FAIL|IGNORE|SETERROR(but continue) */
1320          xsize = -1;
1321          goto jleave;
1322       }
1323       in = out;
1324       out.s = NULL;
1325       dflags &= ~_TD_BUFCOPY;
1326    }
1327 #endif
1328 
1329 jinrest:
1330    if(inrest != NULL && inrest->l > 0){
1331       if(size == 0){
1332          in = *inrest;
1333          inrest->s = NULL;
1334          inrest->l = 0;
1335       }else{
1336          out.s = n_alloc(in.l + inrest->l + 1);
1337          su_mem_copy(out.s, inrest->s, inrest->l);
1338          if(in.l > 0)
1339             su_mem_copy(&out.s[inrest->l], in.s, in.l);
1340          if(in.s != ptr)
1341             n_free(in.s);
1342          (in.s = out.s)[in.l += inrest->l] = '\0';
1343          inrest->l = 0;
1344          out.s = NULL;
1345       }
1346       dflags &= ~_TD_BUFCOPY;
1347    }
1348 
1349 jconvert:
1350    __mimemw_sig = 0;
1351    __mimemw_opipe = safe_signal(SIGPIPE, &__mimemw_onsig);
1352    if (sigsetjmp(__mimemw_actjmp, 1))
1353       goto jleave;
1354 
1355    switch (convert) {
1356    case CONV_FROMQP:
1357       if(!qp_decode_part(&out, &in, outrest, inrest)){
1358          n_err(_("Invalid Quoted-Printable encoding ignored\n"));
1359          xsize = 0; /* TODO size = -1 stops outer levels! */
1360          break;
1361       }
1362       goto jqpb64_dec;
1363    case CONV_TOQP:
1364       if(qp_encode(&out, &in, QP_NONE) == NULL){
1365          xsize = 0; /* TODO size = -1 stops outer levels! */
1366          break;
1367       }
1368       goto jqpb64_enc;
1369    case CONV_8BIT:
1370       xsize = quoteflt_push(qf, in.s, in.l);
1371       break;
1372    case CONV_FROMB64:
1373       if(!b64_decode_part(&out, &in, outrest, inrest))
1374          goto jeb64;
1375       outrest = NULL;
1376       if(0){
1377       /* FALLTHRU */
1378    case CONV_FROMB64_T:
1379          if(!b64_decode_part(&out, &in, outrest, inrest)){
1380 jeb64:
1381             n_err(_("Invalid Base64 encoding ignored\n"));
1382             xsize = 0; /* TODO size = -1 stops outer levels! */
1383             break;
1384          }
1385       }
1386 jqpb64_dec:
1387       if ((xsize = out.l) != 0)
1388          xsize = _fwrite_td(&out, (dflags & ~_TD_BUFCOPY), outrest, qf);
1389       break;
1390    case CONV_TOB64:
1391       /* TODO hack which is necessary unless this is a filter based approach
1392        * TODO and each filter has its own buffer (as necessary): we must not
1393        * TODO pass through a number of bytes which causes padding, otherwise we
1394        * TODO produce multiple adjacent base64 streams, and that is not treated
1395        * TODO in the same relaxed fashion like completely bogus bytes by at
1396        * TODO least mutt and OpenSSL.  So we need an expensive workaround
1397        * TODO unless we have input->iconv->base64 filter chain as such!! :( */
1398       if(size != 0 && /* for Coverity, else ASSERT() */ inrest != NULL){
1399          if(in.l > B64_ENCODE_INPUT_PER_LINE){
1400             uz i;
1401 
1402             i = in.l % B64_ENCODE_INPUT_PER_LINE;
1403             in.l -= i;
1404 
1405             if(i != 0){
1406                ASSERT(inrest->l == 0);
1407                inrest->s = n_realloc(inrest->s, i +1);
1408                su_mem_copy(inrest->s, &in.s[in.l], i);
1409                inrest->s[inrest->l = i] = '\0';
1410             }
1411          }else if(in.l < B64_ENCODE_INPUT_PER_LINE){
1412             inrest->s = n_realloc(inrest->s, in.l +1);
1413             su_mem_copy(inrest->s, in.s, in.l);
1414             inrest->s[inrest->l = in.l] = '\0';
1415             in.l = 0;
1416             xsize = 0;
1417             break;
1418          }
1419       }
1420       if(b64_encode(&out, &in, B64_LF | B64_MULTILINE) == NULL){
1421          xsize = -1;
1422          break;
1423       }
1424 jqpb64_enc:
1425       xsize = fwrite(out.s, sizeof *out.s, out.l, f);
1426       if (xsize != (sz)out.l)
1427          xsize = -1;
1428       break;
1429    case CONV_FROMHDR:
1430       mime_fromhdr(&in, &out, TD_ISPR | TD_ICONV | (dflags & TD_DELCTRL));
1431       xsize = quoteflt_push(qf, out.s, out.l);
1432       break;
1433    case CONV_TOHDR:
1434       xsize = mime_write_tohdr(&in, f, NULL, a_MIME_SH_NONE);
1435       break;
1436    case CONV_TOHDR_A:{
1437       uz col;
1438 
1439       if(dflags & _TD_BUFCOPY){
1440          n_str_dup(&out, &in);
1441          in = out;
1442          out.s = NULL;
1443          dflags &= ~_TD_BUFCOPY;
1444       }
1445       col = 0;
1446       xsize = mime_write_tohdr_a(&in, f, &col, a_MIME_SH_NONE);
1447       }break;
1448    default:
1449       xsize = _fwrite_td(&in, dflags, NULL, qf);
1450       break;
1451    }
1452 
1453 jleave:
1454    if (out.s != NULL)
1455       n_free(out.s);
1456    if (in.s != ptr)
1457       n_free(in.s);
1458    safe_signal(SIGPIPE, __mimemw_opipe);
1459    if (__mimemw_sig != 0)
1460       n_raise(__mimemw_sig);
1461    NYD_OU;
1462    return xsize;
1463 }
1464 
1465 #include "su/code-ou.h"
1466 /* s-it-mode */
1467