Home | History | Annotate | Line # | Download | only in dev
midictl.c revision 1.8
      1  1.8     joerg /* $NetBSD: midictl.c,v 1.8 2015/08/28 13:04:29 joerg Exp $ */
      2  1.2      chap 
      3  1.2      chap /*-
      4  1.7  jmcneill  * Copyright (c) 2006, 2008 The NetBSD Foundation, Inc.
      5  1.2      chap  * All rights reserved.
      6  1.2      chap  *
      7  1.2      chap  * This code is derived from software contributed to The NetBSD Foundation
      8  1.7  jmcneill  * by Chapman Flack, and by Andrew Doran.
      9  1.2      chap  *
     10  1.2      chap  * Redistribution and use in source and binary forms, with or without
     11  1.2      chap  * modification, are permitted provided that the following conditions
     12  1.2      chap  * are met:
     13  1.2      chap  * 1. Redistributions of source code must retain the above copyright
     14  1.2      chap  *    notice, this list of conditions and the following disclaimer.
     15  1.2      chap  * 2. Redistributions in binary form must reproduce the above copyright
     16  1.2      chap  *    notice, this list of conditions and the following disclaimer in the
     17  1.2      chap  *    documentation and/or other materials provided with the distribution.
     18  1.2      chap  *
     19  1.2      chap  * THIS SOFTWARE IS PROVIDED BY THE NETBSD FOUNDATION, INC. AND CONTRIBUTORS
     20  1.2      chap  * ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
     21  1.2      chap  * TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
     22  1.2      chap  * PURPOSE ARE DISCLAIMED.  IN NO EVENT SHALL THE FOUNDATION OR CONTRIBUTORS
     23  1.2      chap  * BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
     24  1.2      chap  * CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
     25  1.2      chap  * SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
     26  1.2      chap  * INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
     27  1.2      chap  * CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
     28  1.2      chap  * ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
     29  1.2      chap  * POSSIBILITY OF SUCH DAMAGE.
     30  1.2      chap  */
     31  1.2      chap #include <sys/cdefs.h>
     32  1.8     joerg __KERNEL_RCSID(0, "$NetBSD: midictl.c,v 1.8 2015/08/28 13:04:29 joerg Exp $");
     33  1.2      chap 
     34  1.2      chap /*
     35  1.2      chap  * See midictl.h for an overview of the purpose and use of this module.
     36  1.2      chap  */
     37  1.2      chap 
     38  1.2      chap #include <sys/systm.h>
     39  1.2      chap #include <sys/types.h>
     40  1.7  jmcneill #include <sys/param.h>
     41  1.7  jmcneill #include <sys/kernel.h>
     42  1.7  jmcneill #include <sys/kthread.h>
     43  1.7  jmcneill #include <sys/kmem.h>
     44  1.2      chap 
     45  1.2      chap #include "midictl.h"
     46  1.2      chap 
     47  1.2      chap /*
     48  1.2      chap  * The upper part of this file is MIDI-aware, and deals with things like
     49  1.2      chap  * decoding MIDI Control Change messages, dealing with the ones that require
     50  1.2      chap  * special handling as mode messages or parameter updates, and so on.
     51  1.2      chap  *
     52  1.2      chap  * It relies on a "store" layer (implemented in the lower part of this file)
     53  1.2      chap  * that only must be able to stash away 2-, 8-, or 16-bit quantities (which
     54  1.2      chap  * it may pack into larger units as it sees fit) and find them again given
     55  1.2      chap  * a class, channel, and key (controller/parameter number).
     56  1.2      chap  *
     57  1.2      chap  * The MIDI controllers can have 1-, 7-, or 14-bit values; the parameters are
     58  1.2      chap  * also 14-bit. The 14-bit values have to be set in two MIDI messages, 7 bits
     59  1.2      chap  * at a time. The MIDI layer uses store-managed 2- or 8-bit slots for the
     60  1.2      chap  * smaller types, and uses the free high bit to indicate that it has explicitly
     61  1.2      chap  * set the value. (Because the store is allowed to pack things, it may 'find'
     62  1.2      chap  * a zero entry for a value we never set, because it shares a word with a
     63  1.2      chap  * different value that has been set. We know it is not a real value because
     64  1.2      chap  * the high bit is clear.)
     65  1.2      chap  *
     66  1.2      chap  * The 14-bit values are handled similarly: 16-bit store slots are used to hold
     67  1.2      chap  * them, with the two free high bits indicating independently whether the MSB
     68  1.2      chap  * and the LSB have been explicitly set--as two separate MIDI messages are
     69  1.2      chap  * required. If such a control is queried when only one half has been explicitly
     70  1.2      chap  * set, the result is as if it had been set to the specified default value
     71  1.2      chap  * before the explicit set.
     72  1.2      chap  */
     73  1.2      chap 
     74  1.2      chap typedef enum { CTL1, CTL7, CTL14, RPN, NRPN } class;
     75  1.2      chap 
     76  1.2      chap /*
     77  1.2      chap  * assert(does_not_apply(KNFNamespaceArgumentAgainstNamesInPrototypes,
     78  1.2      chap  *    PrototypesOfStaticFunctionsWithinNonIncludedFile));
     79  1.2      chap  */
     80  1.2      chap static void reset_all_controllers(midictl *mc, uint_fast8_t chan);
     81  1.2      chap static void enter14(midictl *mc, uint_fast8_t chan, class c,
     82  1.2      chap                     uint_fast16_t key, _Bool islsb, uint8_t val);
     83  1.2      chap static uint_fast16_t read14(midictl *mc, uint_fast8_t chan, class c,
     84  1.2      chap                             uint_fast16_t key, uint_fast16_t dflt);
     85  1.2      chap static class classify(uint_fast16_t *key, _Bool *islsb);
     86  1.2      chap static midictl_notify notify_no_one;
     87  1.2      chap 
     88  1.2      chap static _Bool store_locate(midictl_store *s, class c,
     89  1.2      chap                             uint_fast8_t chan, uint_fast16_t key);
     90  1.2      chap /*
     91  1.2      chap  * store_extract and store_update operate on the bucket most recently found
     92  1.2      chap  * by store_locate on this store. That works because reentrancy of midictl
     93  1.2      chap  * functions is limited: they /can/ be reentered during midictl_notify
     94  1.2      chap  * callbacks, but not at other arbitrary times. We never call notify /during/
     95  1.2      chap  * a locate/extract/update transaction.
     96  1.2      chap  */
     97  1.2      chap static uint16_t store_extract(midictl_store *s, class c,
     98  1.2      chap                               uint_fast8_t chan, uint_fast16_t key);
     99  1.2      chap static void store_update(midictl_store *s, class c,
    100  1.2      chap                          uint_fast8_t chan, uint_fast16_t key, uint16_t value);
    101  1.2      chap 
    102  1.2      chap #define PN_SET 0x8000  /* a parameter number has been explicitly set */
    103  1.2      chap #define C14MSET 0x8000 /* MSB of a 14-bit val has been set */
    104  1.2      chap #define C14LSET 0x4000 /* LSB of a 14-bit val has been set */
    105  1.2      chap #define C7_SET 0x80    /* a 7-bit ctl has been set */
    106  1.2      chap #define C1_SET 2       /* a 1-bit ctl has been set */
    107  1.2      chap 
    108  1.7  jmcneill /*
    109  1.7  jmcneill  *   I M P L E M E N T A T I O N     O F     T H E     S T O R E :
    110  1.7  jmcneill  *
    111  1.7  jmcneill  * MIDI defines a metric plethora of possible controllers, registered
    112  1.7  jmcneill  * parameters, and nonregistered parameters: a bit more than 32k possible words
    113  1.7  jmcneill  * to store. The saving grace is that only a handful are likely to appear in
    114  1.7  jmcneill  * typical MIDI data, and only a handful are likely implemented by or
    115  1.7  jmcneill  * interesting to a typical client. So the store implementation needs to be
    116  1.7  jmcneill  * suited to a largish but quite sparse data set.
    117  1.7  jmcneill  *
    118  1.7  jmcneill  * A double-hashed, open address table is used here. Each slot is a uint64
    119  1.7  jmcneill  * that contains the match key (control class|channel|ctl-or-PN-number) as
    120  1.7  jmcneill  * well as the values for two or more channels. CTL14s, RPNs, and NRPNs can
    121  1.7  jmcneill  * be packed two channels to the slot; CTL7s, six channels; and CTL1s get all
    122  1.7  jmcneill  * 16 channels into one slot. The channel value used in the key is the lowest
    123  1.7  jmcneill  * channel stored in the slot. Open addressing is appropriate here because the
    124  1.7  jmcneill  * link fields in a chained approach would be at least 100% overhead, and also,
    125  1.7  jmcneill  * we don't delete (MIDICTL_RESET is the only event that logically deletes
    126  1.7  jmcneill  * things, and at the moment it does not remove anything from the table, but
    127  1.7  jmcneill  * zeroes the stored value). If wanted, the deletion algorithm for open
    128  1.7  jmcneill  * addressing could be used, with shrinking/rehashing when the load factor
    129  1.7  jmcneill  * drops below 3/8 (1/2 is the current threshold for expansion), and the
    130  1.7  jmcneill  * rehashing would relieve the fills-with-DELETED problem in most cases. But
    131  1.7  jmcneill  * for now the table never shrinks while the device is open.
    132  1.7  jmcneill  */
    133  1.7  jmcneill 
    134  1.7  jmcneill struct midictl_store {
    135  1.7  jmcneill 	uint64_t *table;
    136  1.7  jmcneill 	uint64_t key;
    137  1.7  jmcneill 	uint32_t idx;
    138  1.7  jmcneill 	uint32_t lgcapacity;
    139  1.7  jmcneill 	uint32_t used;
    140  1.7  jmcneill 	kcondvar_t cv;
    141  1.7  jmcneill 	kmutex_t *lock;
    142  1.7  jmcneill 	bool destroy;
    143  1.2      chap };
    144  1.2      chap 
    145  1.7  jmcneill #define INITIALLGCAPACITY 6 /* initial capacity 1<<6 */
    146  1.7  jmcneill #define IS_USED 1<<15
    147  1.7  jmcneill #define IS_CTL7 1<<14
    148  1.7  jmcneill 
    149  1.7  jmcneill #define CTL1SHIFT(chan) (23+((chan)<<1))
    150  1.7  jmcneill #define CTL7SHIFT(chan) (16+((chan)<<3))
    151  1.7  jmcneill #define CTLESHIFT(chan) (23+((chan)<<4))
    152  1.7  jmcneill 
    153  1.7  jmcneill #define	NEED_REHASH(s)	((s)->used * 2 >= 1 << (s)->lgcapacity)
    154  1.2      chap 
    155  1.7  jmcneill static uint_fast8_t const packing[] = {
    156  1.7  jmcneill 	[CTL1 ] = 16, /* 16 * 2 bits ==> 32 bits, all chns in one bucket */
    157  1.7  jmcneill 	[CTL7 ] =  6, /*  6 * 8 bits ==> 48 bits, 6 chns in one bucket */
    158  1.7  jmcneill 	[CTL14] =  2, /*  2 *16 bits ==> 32 bits, 2 chns in one bucket */
    159  1.7  jmcneill 	[RPN  ] =  2,
    160  1.7  jmcneill 	[NRPN ] =  2
    161  1.2      chap };
    162  1.2      chap 
    163  1.7  jmcneill static uint32_t store_idx(uint32_t lgcapacity,
    164  1.7  jmcneill 			  uint64_t *table,
    165  1.7  jmcneill                           uint64_t key, uint64_t mask);
    166  1.7  jmcneill static void store_rehash(midictl_store *s);
    167  1.7  jmcneill static void store_thread(void *);
    168  1.7  jmcneill 
    169  1.2      chap int
    170  1.7  jmcneill midictl_open(midictl *mc)
    171  1.2      chap {
    172  1.7  jmcneill 	midictl_store *s;
    173  1.7  jmcneill 	int error;
    174  1.2      chap 
    175  1.7  jmcneill 	if (mc->lock == NULL)
    176  1.7  jmcneill 		panic("midictl_open: no lock");
    177  1.7  jmcneill 	if (NULL == mc->notify)
    178  1.2      chap 		mc->notify = notify_no_one;
    179  1.7  jmcneill 	s = kmem_zalloc(sizeof(*s), KM_SLEEP);
    180  1.7  jmcneill 	if (s == NULL) {
    181  1.7  jmcneill 		return ENOMEM;
    182  1.7  jmcneill 	}
    183  1.7  jmcneill 	s->lgcapacity = INITIALLGCAPACITY;
    184  1.7  jmcneill 	s->table = kmem_zalloc(sizeof(*s->table)<<s->lgcapacity, KM_SLEEP);
    185  1.7  jmcneill 	if (s->table == NULL) {
    186  1.7  jmcneill 		kmem_free(s->table, sizeof(*s->table)<<s->lgcapacity);
    187  1.7  jmcneill 		kmem_free(s, sizeof(*s));
    188  1.7  jmcneill 		return ENOMEM;
    189  1.7  jmcneill 	}
    190  1.7  jmcneill 	s->lock = mc->lock;
    191  1.7  jmcneill 	cv_init(&s->cv, "midictlv");
    192  1.7  jmcneill 	error = kthread_create(PRI_NONE, KTHREAD_MPSAFE, NULL, store_thread,
    193  1.7  jmcneill 	    s, NULL, "midictlt");
    194  1.7  jmcneill 	if (error != 0) {
    195  1.7  jmcneill 		printf("midictl: cannot create kthread, error = %d\n", error);
    196  1.7  jmcneill 		cv_destroy(&s->cv);
    197  1.7  jmcneill 		kmem_free(s->table, sizeof(*s->table)<<s->lgcapacity);
    198  1.7  jmcneill 		kmem_free(s, sizeof(*s));
    199  1.7  jmcneill 		return error;
    200  1.7  jmcneill 	}
    201  1.7  jmcneill 	mc->store = s;
    202  1.7  jmcneill 	return 0;
    203  1.2      chap }
    204  1.2      chap 
    205  1.2      chap void
    206  1.2      chap midictl_close(midictl *mc)
    207  1.2      chap {
    208  1.7  jmcneill 	midictl_store *s;
    209  1.7  jmcneill 	kmutex_t *lock;
    210  1.7  jmcneill 
    211  1.7  jmcneill 	s = mc->store;
    212  1.7  jmcneill 	lock = s->lock;
    213  1.7  jmcneill 
    214  1.7  jmcneill 	mutex_enter(lock);
    215  1.7  jmcneill 	s->destroy = true;
    216  1.7  jmcneill 	cv_broadcast(&s->cv);
    217  1.7  jmcneill 	mutex_exit(lock);
    218  1.2      chap }
    219  1.2      chap 
    220  1.2      chap void
    221  1.2      chap midictl_change(midictl *mc, uint_fast8_t chan, uint8_t *ctlval)
    222  1.2      chap {
    223  1.2      chap 	class c;
    224  1.2      chap 	uint_fast16_t key, val;
    225  1.2      chap 	_Bool islsb, present;
    226  1.7  jmcneill 
    227  1.7  jmcneill 	KASSERT(mutex_owned(mc->lock));
    228  1.7  jmcneill 	KASSERT(!mc->store->destroy);
    229  1.2      chap 
    230  1.2      chap 	switch ( ctlval[0] ) {
    231  1.2      chap 	/*
    232  1.2      chap 	 * Channel mode messages:
    233  1.2      chap 	 */
    234  1.2      chap 	case MIDI_CTRL_OMNI_OFF:
    235  1.2      chap 	case MIDI_CTRL_OMNI_ON:
    236  1.2      chap 	case MIDI_CTRL_POLY_OFF:
    237  1.2      chap 	case MIDI_CTRL_POLY_ON:
    238  1.2      chap 		if ( chan != mc->base_channel )
    239  1.2      chap 			return; /* ignored - not on base channel */
    240  1.2      chap 		else
    241  1.2      chap 			return; /* XXX ignored anyway - not implemented yet */
    242  1.2      chap 	case MIDI_CTRL_NOTES_OFF:
    243  1.2      chap 		mc->notify(mc->cookie, MIDICTL_NOTES_OFF, chan, 0);
    244  1.2      chap 		return;
    245  1.2      chap 	case MIDI_CTRL_LOCAL:
    246  1.2      chap 		mc->notify(mc->cookie, MIDICTL_LOCAL, chan, ctlval[1]);
    247  1.2      chap 		return;
    248  1.2      chap 	case MIDI_CTRL_SOUND_OFF:
    249  1.2      chap 		mc->notify(mc->cookie, MIDICTL_SOUND_OFF, chan, 0);
    250  1.2      chap 		return;
    251  1.2      chap 	case MIDI_CTRL_RESET:
    252  1.2      chap 		reset_all_controllers(mc, chan);
    253  1.2      chap 		return;
    254  1.2      chap 	/*
    255  1.2      chap 	 * Control changes to be handled specially:
    256  1.2      chap 	 */
    257  1.2      chap 	case MIDI_CTRL_RPN_LSB:
    258  1.2      chap 		mc-> rpn &= ~0x7f;
    259  1.2      chap 		mc-> rpn |=  PN_SET | (0x7f & ctlval[1]);
    260  1.2      chap 		mc->nrpn &= ~PN_SET;
    261  1.2      chap 		return;
    262  1.2      chap 	case MIDI_CTRL_RPN_MSB:
    263  1.8     joerg 		mc-> rpn &= ~0x7fU<<7;
    264  1.2      chap 		mc-> rpn |=  PN_SET | (0x7f & ctlval[1])<<7;
    265  1.2      chap 		mc->nrpn &= ~PN_SET;
    266  1.2      chap 		return;
    267  1.2      chap 	case MIDI_CTRL_NRPN_LSB:
    268  1.2      chap 		mc->nrpn &= ~0x7f;
    269  1.2      chap 		mc->nrpn |=  PN_SET | (0x7f & ctlval[1]);
    270  1.2      chap 		mc-> rpn &= ~PN_SET;
    271  1.2      chap 		return;
    272  1.2      chap 	case MIDI_CTRL_NRPN_MSB:
    273  1.8     joerg 		mc->nrpn &= ~0x7fU<<7;
    274  1.2      chap 		mc->nrpn |=  PN_SET | (0x7f & ctlval[1])<<7;
    275  1.2      chap 		mc-> rpn &= ~PN_SET;
    276  1.2      chap 		return;
    277  1.2      chap 	case MIDI_CTRL_DATA_ENTRY_LSB:
    278  1.2      chap 		islsb = 1;
    279  1.2      chap 		goto whichparm;
    280  1.2      chap 	case MIDI_CTRL_DATA_ENTRY_MSB:
    281  1.2      chap 		islsb = 0;
    282  1.2      chap 	whichparm:
    283  1.2      chap 		if ( 0 == ( (mc->rpn ^ mc->nrpn) & PN_SET ) )
    284  1.2      chap 			return; /* exactly one must be current */
    285  1.2      chap 		if ( mc->rpn & PN_SET ) {
    286  1.2      chap 			key = mc->rpn;
    287  1.2      chap 			c = RPN;
    288  1.2      chap 		} else {
    289  1.2      chap 			key = mc->nrpn;
    290  1.2      chap 			c = NRPN;
    291  1.2      chap 		}
    292  1.2      chap 		key &= 0x3fff;
    293  1.2      chap 		if ( 0x3fff == key ) /* 'null' parm# to lock out changes */
    294  1.2      chap 			return;
    295  1.2      chap 		enter14(mc, chan, c, key, islsb, ctlval[1]);
    296  1.2      chap 		return;
    297  1.2      chap 	case MIDI_CTRL_RPN_INCREMENT: /* XXX for later - these are a PITA to */
    298  1.2      chap 	case MIDI_CTRL_RPN_DECREMENT: /* get right - 'right' varies by param */
    299  1.2      chap 			/* see http://www.midi.org/about-midi/rp18.shtml */
    300  1.2      chap 		return;
    301  1.2      chap 	}
    302  1.2      chap 
    303  1.2      chap 	/*
    304  1.2      chap 	 * Channel mode, RPN, and NRPN operations have been ruled out.
    305  1.2      chap 	 * This is an ordinary control change.
    306  1.2      chap 	 */
    307  1.2      chap 
    308  1.2      chap 	key = ctlval[0];
    309  1.2      chap 	c = classify(&key, &islsb);
    310  1.2      chap 
    311  1.2      chap 	switch ( c ) {
    312  1.2      chap 	case CTL14:
    313  1.2      chap 		enter14(mc, chan, c, key, islsb, ctlval[1]);
    314  1.2      chap 		return;
    315  1.2      chap 	case CTL7:
    316  1.2      chap 		present = store_locate(mc->store, c, chan, key);
    317  1.2      chap 		if ( !mc->accept_any_ctl_rpn ) {
    318  1.2      chap 			if ( !present )
    319  1.2      chap 				break;
    320  1.2      chap 			val = store_extract(mc->store, c, chan, key);
    321  1.2      chap 			if ( !(val&C7_SET) )
    322  1.2      chap 				break;
    323  1.2      chap 		}
    324  1.2      chap 		store_update(mc->store, c, chan, key,
    325  1.2      chap 		    C7_SET | (0x7f & ctlval[1]));
    326  1.2      chap 		mc->notify(mc->cookie, MIDICTL_CTLR, chan, key);
    327  1.2      chap 		return;
    328  1.2      chap 	case CTL1:
    329  1.2      chap 		present = store_locate(mc->store, c, chan, key);
    330  1.2      chap 		if ( !mc->accept_any_ctl_rpn ) {
    331  1.2      chap 			if ( !present )
    332  1.2      chap 				break;
    333  1.2      chap 			val = store_extract(mc->store, c, chan, key);
    334  1.2      chap 			if ( !(val&C1_SET) )
    335  1.2      chap 				break;
    336  1.2      chap 		}
    337  1.2      chap 		store_update(mc->store, c, chan, key,
    338  1.2      chap 		    C1_SET | (ctlval[1]>63));
    339  1.2      chap 		mc->notify(mc->cookie, MIDICTL_CTLR, chan, key);
    340  1.2      chap 		return;
    341  1.2      chap 	case RPN:
    342  1.2      chap 	case NRPN:
    343  1.2      chap 		return; /* won't see these - sop for gcc */
    344  1.2      chap 	}
    345  1.2      chap }
    346  1.2      chap 
    347  1.2      chap uint_fast16_t
    348  1.2      chap midictl_read(midictl *mc, uint_fast8_t chan, uint_fast8_t ctlr,
    349  1.2      chap              uint_fast16_t dflt)
    350  1.2      chap {
    351  1.2      chap 	uint_fast16_t key, val;
    352  1.2      chap 	class c;
    353  1.2      chap 	_Bool islsb, present;
    354  1.7  jmcneill 
    355  1.7  jmcneill 	KASSERT(mutex_owned(mc->lock));
    356  1.7  jmcneill 	KASSERT(!mc->store->destroy);
    357  1.2      chap 
    358  1.2      chap 	key = ctlr;
    359  1.2      chap 	c = classify(&key, &islsb);
    360  1.2      chap 	switch ( c ) {
    361  1.2      chap 	case CTL1:
    362  1.2      chap 		present = store_locate(mc->store, c, chan, key);
    363  1.2      chap 		if ( !present ||
    364  1.2      chap 		    !(C1_SET&(val = store_extract(mc->store, c, chan, key))) ) {
    365  1.2      chap 			val = C1_SET | (dflt > 63); /* convert to boolean */
    366  1.2      chap 			store_update(mc->store, c, chan, key, val);
    367  1.2      chap 		}
    368  1.2      chap 		return (val & 1) ? 127 : 0;
    369  1.2      chap 	case CTL7:
    370  1.2      chap 		present = store_locate(mc->store, c, chan, key);
    371  1.2      chap 		if ( !present ||
    372  1.2      chap 		    !(C7_SET&(val = store_extract(mc->store, c, chan, key))) ) {
    373  1.2      chap 			val = C7_SET | (dflt & 0x7f);
    374  1.2      chap 			store_update(mc->store, c, chan, key, val);
    375  1.2      chap 		}
    376  1.2      chap 		return val & 0x7f;
    377  1.2      chap 	case CTL14:
    378  1.7  jmcneill 		KASSERT(!islsb);
    379  1.2      chap 		return read14(mc, chan, c, key, dflt);
    380  1.2      chap 	case RPN:
    381  1.2      chap 	case NRPN:
    382  1.2      chap 		break; /* sop for gcc */
    383  1.2      chap 	}
    384  1.2      chap 	return 0; /* sop for gcc */
    385  1.2      chap }
    386  1.2      chap 
    387  1.2      chap uint_fast16_t
    388  1.2      chap midictl_rpn_read(midictl *mc, uint_fast8_t chan, uint_fast16_t ctlr,
    389  1.2      chap                  uint_fast16_t dflt)
    390  1.2      chap {
    391  1.7  jmcneill 
    392  1.7  jmcneill 	KASSERT(mutex_owned(mc->lock));
    393  1.7  jmcneill 	KASSERT(!mc->store->destroy);
    394  1.7  jmcneill 
    395  1.2      chap 	return read14(mc, chan, RPN, ctlr, dflt);
    396  1.2      chap }
    397  1.2      chap 
    398  1.2      chap uint_fast16_t
    399  1.2      chap midictl_nrpn_read(midictl *mc, uint_fast8_t chan, uint_fast16_t ctlr,
    400  1.2      chap                   uint_fast16_t dflt)
    401  1.2      chap {
    402  1.7  jmcneill 
    403  1.7  jmcneill 	KASSERT(mutex_owned(mc->lock));
    404  1.7  jmcneill 	KASSERT(!mc->store->destroy);
    405  1.7  jmcneill 
    406  1.2      chap 	return read14(mc, chan, NRPN, ctlr, dflt);
    407  1.2      chap }
    408  1.2      chap 
    409  1.2      chap static void
    410  1.2      chap reset_all_controllers(midictl *mc, uint_fast8_t chan)
    411  1.2      chap {
    412  1.2      chap 	uint_fast16_t ctlr, key;
    413  1.2      chap 	class c;
    414  1.2      chap 	_Bool islsb, present;
    415  1.7  jmcneill 
    416  1.7  jmcneill 	KASSERT(mutex_owned(mc->lock));
    417  1.2      chap 
    418  1.2      chap 	for ( ctlr = 0 ; ; ++ ctlr ) {
    419  1.2      chap 		switch ( ctlr ) {
    420  1.2      chap 		/*
    421  1.2      chap 		 * exempt by http://www.midi.org/about-midi/rp15.shtml:
    422  1.2      chap 		 */
    423  1.2      chap 		case MIDI_CTRL_BANK_SELECT_MSB:		/* 0 */
    424  1.2      chap 		case MIDI_CTRL_CHANNEL_VOLUME_MSB:	/* 7 */
    425  1.2      chap 		case MIDI_CTRL_PAN_MSB:			/* 10 */
    426  1.2      chap 			continue;
    427  1.2      chap 		case MIDI_CTRL_BANK_SELECT_LSB:		/* 32 */
    428  1.2      chap 			ctlr += 31; /* skip all these LSBs anyway */
    429  1.2      chap 			continue;
    430  1.2      chap 		case MIDI_CTRL_SOUND_VARIATION:		/* 70 */
    431  1.2      chap 			ctlr += 9; /* skip all Sound Controllers */
    432  1.2      chap 			continue;
    433  1.2      chap 		case MIDI_CTRL_EFFECT_DEPTH_1:		/* 91 */
    434  1.2      chap 			goto loop_exit; /* nothing more gets reset */
    435  1.2      chap 		/*
    436  1.2      chap 		 * exempt for our own personal reasons:
    437  1.2      chap 		 */
    438  1.2      chap 		case MIDI_CTRL_DATA_ENTRY_MSB:		/* 6 */
    439  1.2      chap 			continue; /* doesn't go to the store */
    440  1.2      chap 		}
    441  1.2      chap 
    442  1.2      chap 		key = ctlr;
    443  1.2      chap 		c = classify(&key, &islsb);
    444  1.2      chap 
    445  1.2      chap 		present = store_locate(mc->store, c, chan, key);
    446  1.2      chap 		if ( !present )
    447  1.2      chap 			continue;
    448  1.2      chap 		store_update(mc->store, c, chan, key, 0); /* no C*SET */
    449  1.2      chap 	}
    450  1.2      chap loop_exit:
    451  1.2      chap 	mc->notify(mc->cookie, MIDICTL_RESET, chan, 0);
    452  1.2      chap }
    453  1.2      chap 
    454  1.2      chap static void
    455  1.2      chap enter14(midictl *mc, uint_fast8_t chan, class c, uint_fast16_t key,
    456  1.2      chap         _Bool islsb, uint8_t val)
    457  1.2      chap {
    458  1.2      chap 	uint16_t stval;
    459  1.2      chap 	_Bool present;
    460  1.2      chap 
    461  1.7  jmcneill 	KASSERT(mutex_owned(mc->lock));
    462  1.7  jmcneill 
    463  1.2      chap 	present = store_locate(mc->store, c, chan, key);
    464  1.2      chap 	stval = (present) ? store_extract(mc->store, c, chan, key) : 0;
    465  1.2      chap 	if ( !( stval & (C14MSET|C14LSET) ) ) {
    466  1.2      chap 		if ( !((NRPN==c)? mc->accept_any_nrpn: mc->accept_any_ctl_rpn) )
    467  1.2      chap 			return;
    468  1.2      chap 	}
    469  1.2      chap 	if ( islsb )
    470  1.2      chap 		stval = C14LSET | val | ( stval & ~0x7f );
    471  1.2      chap 	else
    472  1.2      chap 		stval = C14MSET | ( val << 7 ) | ( stval & ~0x3f80 );
    473  1.2      chap 	store_update(mc->store, c, chan, key, stval);
    474  1.2      chap 	mc->notify(mc->cookie, CTL14 == c ? MIDICTL_CTLR
    475  1.2      chap 		             : RPN   == c ? MIDICTL_RPN
    476  1.2      chap 			     : MIDICTL_NRPN, chan, key);
    477  1.2      chap }
    478  1.2      chap 
    479  1.2      chap static uint_fast16_t
    480  1.2      chap read14(midictl *mc, uint_fast8_t chan, class c, uint_fast16_t key,
    481  1.2      chap        uint_fast16_t dflt)
    482  1.2      chap {
    483  1.2      chap 	uint16_t val;
    484  1.2      chap 	_Bool present;
    485  1.7  jmcneill 
    486  1.7  jmcneill 	KASSERT(mutex_owned(mc->lock));
    487  1.7  jmcneill 
    488  1.2      chap 	present = store_locate(mc->store, c, chan, key);
    489  1.2      chap 	if ( !present )
    490  1.2      chap 		goto neitherset;
    491  1.2      chap 
    492  1.2      chap 	val = store_extract(mc->store, c, chan, key);
    493  1.2      chap 	switch ( val & (C14MSET|C14LSET) ) {
    494  1.2      chap 	case C14MSET|C14LSET:
    495  1.2      chap 		return val & 0x3fff;
    496  1.2      chap 	case C14MSET:
    497  1.2      chap 		val = C14LSET | (val & ~0x7f) | (dflt & 0x7f);
    498  1.2      chap 		break;
    499  1.2      chap 	case C14LSET:
    500  1.2      chap 		val = C14MSET | (val & ~0x3f8) | (dflt & 0x3f8);
    501  1.2      chap 		break;
    502  1.2      chap neitherset:
    503  1.2      chap 	case 0:
    504  1.2      chap 		val = C14MSET|C14LSET | (dflt & 0x3fff);
    505  1.2      chap 	}
    506  1.2      chap 	store_update(mc->store, c, chan, key, val);
    507  1.2      chap 	return val & 0x3fff;
    508  1.2      chap }
    509  1.2      chap 
    510  1.2      chap /*
    511  1.2      chap  * Determine the controller class; ranges based on
    512  1.2      chap  * http://www.midi.org/about-midi/table3.shtml dated 1995/1999/2002
    513  1.2      chap  * and viewed 2 June 2006.
    514  1.2      chap  */
    515  1.2      chap static class
    516  1.2      chap classify(uint_fast16_t *key, _Bool *islsb) {
    517  1.2      chap 	if ( *key < 32 ) {
    518  1.2      chap 		*islsb = 0;
    519  1.2      chap 		return CTL14;
    520  1.2      chap 	} else if ( *key < 64 ) {
    521  1.2      chap 		*islsb = 1;
    522  1.2      chap 		*key -= 32;
    523  1.2      chap 		return CTL14;
    524  1.2      chap 	} else if ( *key < 70 ) {
    525  1.2      chap 		return CTL1;
    526  1.2      chap 	}	  	/* 70-84 defined, 85-90 undef'd, 91-95 def'd */
    527  1.2      chap 	return CTL7;	/* 96-101,120- handled above, 102-119 all undef'd */
    528  1.2      chap 		  	/* treat them all as CTL7 */
    529  1.2      chap }
    530  1.2      chap 
    531  1.2      chap static void
    532  1.4  christos notify_no_one(void *cookie, midictl_evt evt,
    533  1.4  christos     uint_fast8_t chan, uint_fast16_t k)
    534  1.2      chap {
    535  1.2      chap }
    536  1.2      chap 
    537  1.2      chap #undef PN_SET
    538  1.2      chap #undef C14MSET
    539  1.2      chap #undef C14LSET
    540  1.2      chap #undef C7_SET
    541  1.2      chap #undef C1_SET
    542  1.2      chap 
    543  1.7  jmcneill static void
    544  1.7  jmcneill store_thread(void *arg)
    545  1.2      chap {
    546  1.2      chap 	midictl_store *s;
    547  1.2      chap 
    548  1.7  jmcneill 	s = arg;
    549  1.7  jmcneill 
    550  1.7  jmcneill 	mutex_enter(s->lock);
    551  1.7  jmcneill 	for (;;) {
    552  1.7  jmcneill 		if (s->destroy) {
    553  1.7  jmcneill 			mutex_exit(s->lock);
    554  1.7  jmcneill 			cv_destroy(&s->cv);
    555  1.7  jmcneill 			kmem_free(s->table, sizeof(*s->table)<<s->lgcapacity);
    556  1.7  jmcneill 			kmem_free(s, sizeof(*s));
    557  1.7  jmcneill 			kthread_exit(0);
    558  1.7  jmcneill 		} else if (NEED_REHASH(s)) {
    559  1.7  jmcneill 			store_rehash(s);
    560  1.7  jmcneill 		} else {
    561  1.7  jmcneill 			cv_wait(&s->cv, s->lock);
    562  1.7  jmcneill 		}
    563  1.7  jmcneill 	}
    564  1.2      chap }
    565  1.2      chap 
    566  1.2      chap static _Bool
    567  1.2      chap store_locate(midictl_store *s, class c, uint_fast8_t chan, uint_fast16_t key)
    568  1.2      chap {
    569  1.2      chap 	uint64_t mask;
    570  1.7  jmcneill 
    571  1.7  jmcneill 	KASSERT(mutex_owned(s->lock));
    572  1.2      chap 
    573  1.2      chap 	if ( s->used >= 1 << s->lgcapacity )
    574  1.7  jmcneill 		panic("%s: repeated attempts to expand table failed", __func__);
    575  1.2      chap 
    576  1.2      chap 	chan = packing[c] * (chan/packing[c]);
    577  1.2      chap 
    578  1.2      chap 	if ( CTL7 == c ) {	/* only 16 bits here (key's only 7) */
    579  1.2      chap 		s->key = IS_USED | IS_CTL7 | (chan << 7) | key;
    580  1.2      chap 		mask = 0xffff;
    581  1.2      chap 	} else {		/* use 23 bits (key could be 14) */
    582  1.2      chap 		s->key = (c << 20) | (chan << 16) | IS_USED | key;
    583  1.2      chap 		mask = 0x7fffff;
    584  1.2      chap 	}
    585  1.2      chap 
    586  1.2      chap 	s->idx = store_idx(s->lgcapacity, s->table, s->key, mask);
    587  1.2      chap 
    588  1.2      chap 	if ( !(s->table[s->idx] & IS_USED) )
    589  1.2      chap 		return 0;
    590  1.2      chap 
    591  1.2      chap 	return 1;
    592  1.2      chap }
    593  1.2      chap 
    594  1.2      chap static uint16_t
    595  1.3  christos store_extract(midictl_store *s, class c, uint_fast8_t chan,
    596  1.4  christos     uint_fast16_t key)
    597  1.2      chap {
    598  1.7  jmcneill 
    599  1.7  jmcneill 	KASSERT(mutex_owned(s->lock));
    600  1.7  jmcneill 
    601  1.2      chap 	chan %= packing[c];
    602  1.2      chap 	switch ( c ) {
    603  1.2      chap 	case CTL1:
    604  1.2      chap 		return 3 & (s->table[s->idx]>>CTL1SHIFT(chan));
    605  1.2      chap 	case CTL7:
    606  1.2      chap 		return 0xff & (s->table[s->idx]>>CTL7SHIFT(chan));
    607  1.2      chap 	case CTL14:
    608  1.2      chap 	case RPN:
    609  1.2      chap 	case NRPN:
    610  1.2      chap 		break;
    611  1.2      chap 	}
    612  1.2      chap 	return 0xffff & (s->table[s->idx]>>CTLESHIFT(chan));
    613  1.2      chap }
    614  1.2      chap 
    615  1.2      chap static void
    616  1.2      chap store_update(midictl_store *s, class c, uint_fast8_t chan,
    617  1.4  christos     uint_fast16_t key, uint16_t value)
    618  1.2      chap {
    619  1.2      chap 	uint64_t orig;
    620  1.7  jmcneill 
    621  1.7  jmcneill 	KASSERT(mutex_owned(s->lock));
    622  1.2      chap 
    623  1.2      chap 	orig = s->table[s->idx];
    624  1.2      chap 	if ( !(orig & IS_USED) ) {
    625  1.2      chap 		orig = s->key;
    626  1.2      chap 		++ s->used;
    627  1.2      chap 	}
    628  1.2      chap 
    629  1.2      chap 	chan %= packing[c];
    630  1.2      chap 
    631  1.2      chap 	switch ( c ) {
    632  1.2      chap 	case CTL1:
    633  1.2      chap 		orig &= ~(((uint64_t)3)<<CTL1SHIFT(chan));
    634  1.2      chap 		orig |= ((uint64_t)(3 & value)) << CTL1SHIFT(chan);
    635  1.2      chap 		break;
    636  1.2      chap 	case CTL7:
    637  1.2      chap 		orig &= ~(((uint64_t)0xff)<<CTL7SHIFT(chan));
    638  1.2      chap 		orig |= ((uint64_t)(0xff & value)) << CTL7SHIFT(chan);
    639  1.2      chap 		break;
    640  1.2      chap 	case CTL14:
    641  1.2      chap 	case RPN:
    642  1.2      chap 	case NRPN:
    643  1.2      chap 		orig &= ~(((uint64_t)0xffff)<<CTLESHIFT(chan));
    644  1.2      chap 		orig |= ((uint64_t)value) << CTLESHIFT(chan);
    645  1.2      chap 		break;
    646  1.2      chap 	}
    647  1.2      chap 
    648  1.2      chap 	s->table[s->idx] = orig;
    649  1.7  jmcneill 	if (NEED_REHASH(s))
    650  1.7  jmcneill 		cv_broadcast(&s->cv);
    651  1.2      chap }
    652  1.2      chap 
    653  1.2      chap static uint32_t
    654  1.6  gmcgarry store_idx(uint32_t lgcapacity, uint64_t *table,
    655  1.2      chap           uint64_t key, uint64_t mask)
    656  1.2      chap {
    657  1.2      chap 	uint32_t val;
    658  1.2      chap 	uint32_t k, h1, h2;
    659  1.2      chap 	int32_t idx;
    660  1.2      chap 
    661  1.2      chap 	k = key;
    662  1.2      chap 
    663  1.2      chap 	h1 = ((k * 0x61c88646) >> (32-lgcapacity)) & ((1<<lgcapacity) - 1);
    664  1.2      chap 	h2 = ((k * 0x9e3779b9) >> (32-lgcapacity)) & ((1<<lgcapacity) - 1);
    665  1.2      chap 	h2 |= 1;
    666  1.2      chap 
    667  1.2      chap 	for ( idx = h1 ;; idx -= h2 ) {
    668  1.2      chap 		if ( idx < 0 )
    669  1.2      chap 			idx += 1<<lgcapacity;
    670  1.2      chap 		val = (uint32_t)(table[idx] & mask);
    671  1.2      chap 		if ( val == k )
    672  1.2      chap 			break;
    673  1.2      chap 		if ( !(val & IS_USED) )
    674  1.2      chap 			break;
    675  1.2      chap 	}
    676  1.2      chap 
    677  1.2      chap 	return idx;
    678  1.2      chap }
    679  1.2      chap 
    680  1.2      chap static void
    681  1.2      chap store_rehash(midictl_store *s)
    682  1.2      chap {
    683  1.7  jmcneill 	uint64_t *newtbl, *oldtbl, mask;
    684  1.7  jmcneill 	uint32_t oldlgcap, newlgcap, oidx, nidx;
    685  1.7  jmcneill 
    686  1.7  jmcneill 	KASSERT(mutex_owned(s->lock));
    687  1.7  jmcneill 
    688  1.7  jmcneill 	oldlgcap = s->lgcapacity;
    689  1.7  jmcneill 	newlgcap = oldlgcap + s->lgcapacity;
    690  1.7  jmcneill 
    691  1.7  jmcneill 	mutex_exit(s->lock);
    692  1.7  jmcneill 	newtbl = kmem_zalloc(sizeof(*newtbl) << newlgcap, KM_SLEEP);
    693  1.7  jmcneill 	mutex_enter(s->lock);
    694  1.7  jmcneill 
    695  1.7  jmcneill 	if (newtbl == NULL) {
    696  1.7  jmcneill 		kpause("midictls", false, hz, s->lock);
    697  1.7  jmcneill 		return;
    698  1.7  jmcneill 	}
    699  1.2      chap 	/*
    700  1.7  jmcneill 	 * If s->lgcapacity is changed from what we saved int oldlgcap
    701  1.7  jmcneill 	 * then someone else has already done this for us.
    702  1.7  jmcneill 	 * XXXMRG but only function changes s->lgcapacity from its
    703  1.7  jmcneill 	 * initial value, and it is called singled threaded from the
    704  1.7  jmcneill 	 * main store_thread(), so this code seems dead to me.
    705  1.2      chap 	 */
    706  1.7  jmcneill 	if (oldlgcap != s->lgcapacity) {
    707  1.7  jmcneill 		KASSERT(FALSE);
    708  1.7  jmcneill 		mutex_exit(s->lock);
    709  1.7  jmcneill 		kmem_free(newtbl, sizeof(*newtbl) << newlgcap);
    710  1.7  jmcneill 		mutex_enter(s->lock);
    711  1.2      chap 		return;
    712  1.7  jmcneill 	}
    713  1.7  jmcneill 
    714  1.7  jmcneill 	for (oidx = 1 << s->lgcapacity ; oidx-- > 0 ; ) {
    715  1.7  jmcneill 		if (!(s->table[oidx] & IS_USED))
    716  1.2      chap 			continue;
    717  1.7  jmcneill 		if (s->table[oidx] & IS_CTL7)
    718  1.2      chap 			mask = 0xffff;
    719  1.2      chap 		else
    720  1.2      chap 			mask = 0x3fffff;
    721  1.7  jmcneill 		nidx = store_idx(newlgcap, newtbl,
    722  1.7  jmcneill 		    s->table[oidx] & mask, mask);
    723  1.2      chap 		newtbl[nidx] = s->table[oidx];
    724  1.2      chap 	}
    725  1.7  jmcneill 	oldtbl = s->table;
    726  1.2      chap 	s->table = newtbl;
    727  1.2      chap 	s->lgcapacity = newlgcap;
    728  1.2      chap 
    729  1.7  jmcneill 	mutex_exit(s->lock);
    730  1.7  jmcneill 	kmem_free(oldtbl, sizeof(*oldtbl) << oldlgcap);
    731  1.7  jmcneill 	mutex_enter(s->lock);
    732  1.2      chap }
    733