MIDI writer?

Stéphane Rollandin lecteur at zogotounga.net
Sun Oct 23 17:04:41 UTC 2005


Cees De Groot wrote:
> Hmm... this was a long intro to a simple question: is there a MIDI
> file writer for Squeak floating around somewhere?

there is one by mark guzdial.

attached is a version filed out from my current 3.8 image (I think only 
the category changed). I don't remember where in the web I found it.


Stef
-------------- next part --------------
'From Squeak2.8 of 13 June 2000 [latest update: #2359] on 29 March 2001 at 3:18:37 am'!
Object subclass: #MIDIFileWriter
	instanceVariableNames: 'stream score trackData activeEvents lastEventTime fileData '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Sound-Scores'!
!MIDIFileWriter commentStamp: 'YYL 3/29/2001 03:18' prior: 0!
MIDIFileWriter 1.01
converts a MIDIScore into a midifile...YAY!!
To load in, modify, and save out a midi file, do this:

(scorePlayerMorph _ ScorePlayerMorph onMIDIFileNamed:'inputMidiFile.mid') openInWorld.
"play with the midi file...move notes around, etc."
"when done, do this:"
mfw _ MIDIFileWriter saveFileNamed: 'outputMidiFile.mid' fromScore: ((scorePlayerMorph scorePlayer) score).
mfw writeMidi.


To simply test out how squeak converts your midifile, try this out:

midiScore _ MIDIFileReader scoreFromFileNamed: 'inputMidiFile.mid'
mfw _ MIDIFileWriter saveFileNamed: 'outputMidiFile.mid' fromScore: midiScore.
mfw writeMidi.

questions? comments? bugs? feature requests? code updates? check out the Knowledge Base
http://guzdial.cc.gatech.edu:8080/squeakers.179
gte356h at prism.gatech.edu!


!MIDIFileWriter methodsFor: 'as yet unclassified' stamp: 'YYL 2/25/2001 13:22'!
convertEvent: aMidiEvent
	"converts aMidiEvent into bytes and places them into trackData"

	| eventData "OC of bytes that represent this event" |
	eventData _ OrderedCollection new.
	
	eventData addAllLast: (self noteOffEvents: (aMidiEvent time)).

	"add varLengthInt of event's delta-time to eventData"
	eventData addAllLast: (self varLengthInt: ((aMidiEvent time) - lastEventTime)).
	
	(aMidiEvent isNoteEvent) ifTrue:
		[
		self assert: [(aMidiEvent channel) <= 16r0F].
		self assert: [(aMidiEvent midiKey) <= 16r7F].
		self assert: [(aMidiEvent velocity) <= 16r7F].
		eventData add: (16r90 bitOr: (aMidiEvent channel)).
		eventData add: (aMidiEvent midiKey).
		eventData add: (aMidiEvent velocity).
		activeEvents add: aMidiEvent.
		].
	(aMidiEvent isControlChange) ifTrue:
		[
		self assert: [(aMidiEvent channel) <= 16r0F].
"		self assert: [(aMidiEvent control) <= 16r77].
Midi specs say this must be true...but I have found files that don't adhere to it...so out it goes!!"
		self assert: [(aMidiEvent value) <= 16r7F].
		eventData add: (16rB0 bitOr: (aMidiEvent channel)).
		eventData add: (aMidiEvent control).
		eventData add: (aMidiEvent value).
		].
	(aMidiEvent isPitchBend) ifTrue:
		[ | msb lsb |
		"reverse engineered from MIDIFileReader"
		msb _ (aMidiEvent bend) bitShift: -7. "move msb right 7  and see what it is"
		lsb _ (aMidiEvent bend) - (msb bitShift: 7). 
		eventData add: (16rE0 bitOr: (aMidiEvent channel)).
		eventData add: lsb.
		eventData add: msb.
		].
	(aMidiEvent isProgramChange) ifTrue:
		[
		self assert: [(aMidiEvent channel) <= 16r0F].
		self assert: [(aMidiEvent program) <= 16r7F].
		eventData add: (16rC0 bitOr: (aMidiEvent channel)).
		eventData add: (aMidiEvent program).
		].
	(aMidiEvent isTempoEvent) ifTrue:
		[
		eventData add: 16rFF. eventData add: 16r51. eventData add: 16r03. "TempoEvent meta ID"
		eventData addAllLast: (self get24Bit: (aMidiEvent tempo)).
		].
	lastEventTime _ aMidiEvent time.
	^eventData.! !

!MIDIFileWriter methodsFor: 'as yet unclassified' stamp: 'YYL 1/21/2001 05:42'!
get24Bit: num
	"returns an array of num as a 24-bit number (with leading 0s)"

	| return |
	return _ Array new: 3.
	return at:1 put: (num digitAt: 3).
	return at:2 put: (num digitAt: 2).
	return at:3 put: (num digitAt: 1).
	^return.! !

!MIDIFileWriter methodsFor: 'as yet unclassified' stamp: 'YYL 1/23/2001 22:13'!
noteOffEvents: time
	"returns an ordered collection with the midi file info for all the notes that should be turned off before time"

	| eventData |
	eventData _ OrderedCollection new.
	(activeEvents isEmpty) ifFalse:
	[
		[(activeEvents isEmpty)not and: [time >= ((activeEvents first) endTime)]] whileTrue:
			[ |first|
			first _ activeEvents removeFirst.
			self assert: [(first channel) <= 16r0F].
			self assert: [(first midiKey) <= 16r7F].
			"add varLengthInt of note off's delta-time to eventData"
			eventData addAllLast: (self varLengthInt: ((first endTime) - lastEventTime)).
			eventData add: (16r80 bitOr: (first channel)).
			eventData add: (first midiKey).
			eventData add: 16r40. "default release velocity"
			lastEventTime _ first endTime.
			].
		].
	^eventData.! !

!MIDIFileWriter methodsFor: 'as yet unclassified' stamp: 'YYL 1/23/2001 22:13'!
remainingNoteOffEvents
	"returns an ordered collection with the midi file info for all the remaining notes that should be turned off"

	(activeEvents isEmpty)
	ifFalse:
		[^ self noteOffEvents: ((activeEvents last) endTime).]
	ifTrue:
		[^ OrderedCollection new. "return an empty OC"].! !

!MIDIFileWriter methodsFor: 'as yet unclassified' stamp: 'YYL 1/11/2001 20:42'!
score: aScore

	score _ aScore.! !

!MIDIFileWriter methodsFor: 'as yet unclassified' stamp: 'YYL 1/11/2001 20:40'!
stream: aStream

	stream _ aStream.! !

!MIDIFileWriter methodsFor: 'as yet unclassified' stamp: 'YYL 1/21/2001 05:08'!
type
	"returns the midi file type (0,1,or 2)...right now only 0 and 1 are figured out."

	(((score tracks) size = 1) and: [(score tempoMap) isEmptyOrNil])
		ifTrue: [^0.]
		ifFalse: [^1].! !

!MIDIFileWriter methodsFor: 'as yet unclassified' stamp: 'YYL 1/21/2001 03:56'!
varLengthInt: aNum
	"return an OC of the num as a variable length int"

	"to do: add constraints(4 bytes max), test thouroughly"

	| array count value returnOC|
	value _ aNum.
	array _ Array new: 4.
	count _ 1.
	
	array at: count put: (value bitAnd: 16r7F).
	count _ count + 1.
	value _ (value bitShift: -7).

	[(value = 0)not] whileTrue:
		[
		array at: count put: ((value bitAnd: 16r7F) bitOr: 16r80).
		count _ count + 1.
		value _ (value bitShift: -7).
		].
	count _ count - 1.
	"write out backward"
	returnOC _ OrderedCollection new.
	count to: 1 by: -1 do: [:pos|
		returnOC add: (array at: pos).
		].
	^returnOC.
"   buffer = value & 0x7F; {bitwise & from bottom}

   while ( (value >>= 7) ) {value = value >> 7}
   {
     buffer <<= 8; {buffer = buffer << 8}
     buffer |= ((value & 0x7F) | 0x80);
   }"
! !

!MIDIFileWriter methodsFor: 'as yet unclassified' stamp: 'YYL 1/15/2001 22:57'!
write16Bit: num
	"writes num as a 16-bit number (with leading 0s"

	stream nextPut: (num digitAt: 2).
	stream nextPut: (num digitAt: 1).! !

!MIDIFileWriter methodsFor: 'as yet unclassified' stamp: 'YYL 1/15/2001 22:57'!
write32Bit: num
	"writes num as a 32-bit number (with leading 0s"

	stream nextPut: (num digitAt: 4).
	stream nextPut: (num digitAt: 3).
	stream nextPut: (num digitAt: 2).
	stream nextPut: (num digitAt: 1).! !


!MIDIFileWriter methodsFor: 'chunk writing' stamp: 'YYL 1/21/2001 05:52'!
writeHeaderChunk
	"writes the midi file's header"

	|type|
	type _ self type.
	stream nextPutAll: 'MThd'.
	self write32Bit: 16r06.
	self write16Bit: type.
	(type = 0)
		ifTrue: [self write16Bit: 1.].
	(type = 1)
		ifTrue: [self write16Bit: ((score tracks) size + 1"for TempoMap").].
	self write16Bit: (score ticksPerQuarterNote). "does not support SMPTE"
	! !

!MIDIFileWriter methodsFor: 'chunk writing' stamp: 'YYL 1/23/2001 20:53'!
writeMidi
	"writes the midi file"

	self writeHeaderChunk.
	(self type) = 1 ifTrue:
		[self writeTrackChunk: (score tempoMap) named: 'TempoMap'].
	1 to: ((score tracks) size) do:
	[:trackNo| self writeTrackChunk: ((score tracks) at: trackNo) named: ((score trackInfo) at: trackNo).
	].
	stream close.! !

!MIDIFileWriter methodsFor: 'chunk writing' stamp: 'YYL 3/29/2001 01:46'!
writeTrackChunk: track named: trackName
	| sortedTrack |
	"writes the midi file's Track info"

	trackData _ OrderedCollection new.

	stream nextPutAll: 'MTrk'.
	activeEvents _ SortedCollection new.
	activeEvents sortBlock: [:n1 :n2 | (n1 endTime) <= (n2 endTime)].
	lastEventTime _ 0.

"FIX: March 29,2001: sort track before do each event...this fixes problems with notes being out of order in the track.  Out of order notes lead to writing negative time values in the midi file..a definite no no!!  Added the following line to sort it."
	sortedTrack _ (track asSortedCollection:[:n1 :n2 | (n1 time) <= (n2 time)]) asArray.

	sortedTrack do:"build track info in trackData here"
		[:event|
		trackData addAllLast: (self convertEvent: event).
		].
	trackData addAllLast: (self remainingNoteOffEvents).
	(activeEvents isEmpty) ifFalse: [self error:'still activeEvents left!!'.].
	trackData add: 0. trackData add: 255. trackData add:47. trackData add: 0. "end of track meta-event"
	self write32Bit: (trackData size).
	trackData do:
		[:current |
		stream nextPut: current.
		].
	! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

MIDIFileWriter class
	instanceVariableNames: ''!

!MIDIFileWriter class methodsFor: 'as yet unclassified' stamp: 'YYL 1/15/2001 22:45'!
saveFileNamed: fileName fromScore: aScore

	| t |
	t _ self new.
	t stream: (StandardFileStream newFileNamed: fileName) binary.
	t score: aScore.
	^ t.! !

!MIDIFileWriter class methodsFor: 'as yet unclassified' stamp: 'YYL 1/19/2001 12:37'!
withScore: aScore
"non-functional...for testing only!!"
	| t |
	t _ self new.
	"t stream: (StandardFileStream newFileNamed: 'c:\temp\output.mid') binary."
	t score: aScore.
	^ t.! !


More information about the Squeak-dev mailing list