8 people like it.

Her name is Cherry; we've just met

Third cut of a guitar chord shape generator. Given a fretted instrument with a particular tuning (eg. 6 string guitar tuned EADGBE), the generator will produce the frettings necessary to play any specified chord. This is not done from a chord library, but algorithmically (hence should work with whacky tunings). This version doesn't fully respect the limitations of the human hand beyond specifying a maximum 'stretch' of a few frets, so some of the shapes generated would need a friend to help play them! This will be dealt with in a future version. This third version contains improved handling of differing tunings and instruments (eg. DADGAD; banjo) but still doesn't check for unplayable shapes.

  1: 
  2: 
  3: 
  4: 
  5: 
  6: 
  7: 
  8: 
  9: 
 10: 
 11: 
 12: 
 13: 
 14: 
 15: 
 16: 
 17: 
 18: 
 19: 
 20: 
 21: 
 22: 
 23: 
 24: 
 25: 
 26: 
 27: 
 28: 
 29: 
 30: 
 31: 
 32: 
 33: 
 34: 
 35: 
 36: 
 37: 
 38: 
 39: 
 40: 
 41: 
 42: 
 43: 
 44: 
 45: 
 46: 
 47: 
 48: 
 49: 
 50: 
 51: 
 52: 
 53: 
 54: 
 55: 
 56: 
 57: 
 58: 
 59: 
 60: 
 61: 
 62: 
 63: 
 64: 
 65: 
 66: 
 67: 
 68: 
 69: 
 70: 
 71: 
 72: 
 73: 
 74: 
 75: 
 76: 
 77: 
 78: 
 79: 
 80: 
 81: 
 82: 
 83: 
 84: 
 85: 
 86: 
 87: 
 88: 
 89: 
 90: 
 91: 
 92: 
 93: 
 94: 
 95: 
 96: 
 97: 
 98: 
 99: 
100: 
101: 
102: 
103: 
104: 
105: 
106: 
107: 
108: 
109: 
110: 
111: 
112: 
113: 
114: 
115: 
116: 
117: 
118: 
119: 
120: 
121: 
122: 
123: 
124: 
125: 
126: 
127: 
128: 
129: 
130: 
131: 
132: 
133: 
134: 
135: 
136: 
137: 
138: 
139: 
140: 
141: 
142: 
143: 
144: 
145: 
146: 
147: 
148: 
149: 
150: 
151: 
152: 
153: 
154: 
155: 
156: 
157: 
158: 
159: 
160: 
161: 
162: 
163: 
164: 
165: 
166: 
167: 
168: 
169: 
170: 
171: 
172: 
173: 
174: 
175: 
176: 
177: 
178: 
179: 
180: 
181: 
182: 
183: 
184: 
185: 
186: 
187: 
188: 
189: 
190: 
191: 
192: 
193: 
194: 
195: 
196: 
197: 
198: 
199: 
200: 
201: 
202: 
203: 
204: 
205: 
206: 
207: 
208: 
209: 
210: 
211: 
212: 
213: 
214: 
215: 
216: 
217: 
218: 
219: 
220: 
221: 
222: 
223: 
224: 
225: 
226: 
227: 
228: 
229: 
230: 
231: 
232: 
233: 
234: 
235: 
236: 
237: 
238: 
239: 
240: 
241: 
242: 
243: 
244: 
245: 
246: 
247: 
248: 
249: 
250: 
251: 
252: 
253: 
254: 
255: 
256: 
257: 
258: 
259: 
260: 
261: 
262: 
263: 
264: 
265: 
266: 
267: 
268: 
269: 
270: 
271: 
272: 
273: 
274: 
275: 
276: 
277: 
278: 
279: 
280: 
281: 
282: 
283: 
284: 
285: 
286: 
287: 
288: 
289: 
290: 
291: 
292: 
293: 
294: 
295: 
296: 
297: 
298: 
299: 
300: 
301: 
302: 
303: 
304: 
305: 
306: 
307: 
308: 
309: 
310: 
311: 
312: 
313: 
314: 
315: 
316: 
317: 
318: 
319: 
320: 
321: 
322: 
323: 
324: 
325: 
326: 
327: 
328: 
329: 
330: 
331: 
332: 
333: 
334: 
335: 
336: 
337: 
338: 
339: 
340: 
341: 
342: 
343: 
344: 
345: 
346: 
347: 
348: 
349: 
350: 
351: 
352: 
353: 
354: 
355: 
356: 
357: 
358: 
359: 
360: 
361: 
362: 
363: 
364: 
365: 
366: 
367: 
368: 
369: 
370: 
371: 
372: 
373: 
374: 
375: 
376: 
377: 
378: 
379: 
380: 
381: 
382: 
383: 
384: 
385: 
386: 
387: 
388: 
389: 
390: 
391: 
392: 
393: 
394: 
395: 
396: 
397: 
398: 
399: 
400: 
401: 
402: 
403: 
404: 
405: 
406: 
407: 
408: 
409: 
410: 
// How many semitones in Western music:
let SEMITONES_PER_OCTAVE = 12

// Flat, Natural or Sharp:
type TAccidental = Flat | Natural | Sharp
// A note name, accidental and chromatic index but without specifying the octave it is in - eg. G#, A, or Bb:
type TNoteLabel = {name : char; accidental : TAccidental; chromaticIndex : int}
// A note including its specific octave - eg. G# in octave 2 (from an arbitrary lowest octave):
type TNote = {label : TNoteLabel; octave : int}
// An array of the chromatic indices of notes forming a chord type:
type TChordIndexes = array<int>
// Whether a chord is major or minor:
type TScaleType = Major | Minor
// A Relative Chord in terms of the chromatic indices of its notes - eg. [|0; 4; 7; 12|]; Major is an ordinary
// major chord:
type TChordType = {chordIndexes : TChordIndexes; scaleType : TScaleType}
// An Absolute Chord - eg. C major:
type TChord = array<TNote>
// When translating an index to a readable note, determines whether to prefer the sharp version
// or the flat version when encountering an enharmonic:
type TEnharmonicPreference = PreferFlat | PreferSharp | PreferNeither

// A way of noting which notes have been covered during the generation of a chord:
type TNoteMapping = {mappedNote : TNote; mutable useCount : int}

// How an instrument is tuned - eg. conventional guitar tuning is EADGBE', 'dropped D' tuning is DADGBE'.
type TTuning = array<TNote>

// A combination of string and fret - the actual location of a fingering on the neck:
type TFretting = {stringIndex : int; fretIndex : int}
// A fretting plus the note that would result from that fretting:
type TFrettedNote = {fretting : TFretting; note : TNote}

/// Any fretted instrument:
type TInstrument (fretCount : int, tuning : TTuning) = 
    member this.fretCount = fretCount // Includes nut at 0
    member this.tuning = tuning
    // TODO ensure tuning is the same size as strings

/// All human readable note names, including enharmonics (but not bothering with double-flats, double-sharps):
let allNotes =
    [|
        {name = 'A'; accidental = Natural; chromaticIndex = 0}
        {name = 'A'; accidental = Sharp; chromaticIndex = 1}

        {name = 'B'; accidental = Flat; chromaticIndex = 1}
        {name = 'B'; accidental = Natural; chromaticIndex = 2}
        {name = 'B'; accidental = Sharp; chromaticIndex = 3}

        {name = 'C'; accidental = Flat; chromaticIndex = 2}
        {name = 'C'; accidental = Natural; chromaticIndex = 3}
        {name = 'C'; accidental = Sharp; chromaticIndex = 4}

        {name = 'D'; accidental = Flat; chromaticIndex = 4}
        {name = 'D'; accidental = Natural; chromaticIndex = 5}
        {name = 'D'; accidental = Sharp; chromaticIndex = 6}

        {name = 'E'; accidental = Flat; chromaticIndex = 6}
        {name = 'E'; accidental = Natural; chromaticIndex = 7}
        {name = 'E'; accidental = Sharp; chromaticIndex = 8}

        {name = 'F'; accidental = Flat; chromaticIndex = 7}
        {name = 'F'; accidental = Natural; chromaticIndex = 8}
        {name = 'F'; accidental = Sharp; chromaticIndex = 9}

        {name = 'G'; accidental = Flat; chromaticIndex = 9}
        {name = 'G'; accidental = Natural; chromaticIndex = 10}
        {name = 'G'; accidental = Sharp; chromaticIndex = 11}

        {name = 'A'; accidental = Flat; chromaticIndex = 11}
    |]

/// Some useful constants for notes:
let ANat = {name = 'A'; accidental = Natural; chromaticIndex = 0}
let ASharp = {name = 'A'; accidental = Sharp; chromaticIndex = 1}

let BFlat = {name = 'B'; accidental = Flat; chromaticIndex = 1}
let BNat = {name = 'B'; accidental = Natural; chromaticIndex = 2}
let BSharp = {name = 'B'; accidental = Sharp; chromaticIndex = 3}

let CFlat = {name = 'C'; accidental = Flat; chromaticIndex = 2}
let CNat = {name = 'C'; accidental = Natural; chromaticIndex = 3}
let CSharp = {name = 'C'; accidental = Sharp; chromaticIndex = 4}

let DFlat = {name = 'D'; accidental = Flat; chromaticIndex = 4}
let DNat = {name = 'D'; accidental = Natural; chromaticIndex = 5}
let DSharp = {name = 'D'; accidental = Sharp; chromaticIndex = 6}

let EFlat = {name = 'E'; accidental = Flat; chromaticIndex = 6}
let ENat = {name = 'E'; accidental = Natural; chromaticIndex = 7}
let ESharp = {name = 'E'; accidental = Sharp; chromaticIndex = 8}

let FFlat = {name = 'F'; accidental = Flat; chromaticIndex = 7}
let FNat = {name = 'F'; accidental = Natural; chromaticIndex = 8}
let FSharp = {name = 'F'; accidental = Sharp; chromaticIndex = 9}

let GFlat = {name = 'G'; accidental = Flat; chromaticIndex = 9}
let GNat = {name = 'G'; accidental = Natural; chromaticIndex = 10}
let GSharp = {name = 'G'; accidental = Sharp; chromaticIndex = 11}

let AFlat = {name = 'A'; accidental = Flat; chromaticIndex = 11}

/// An operator to concatenate two arrays:
let (@@) a b =
    Array.concat [a; b]

// Common Relative Chords, in terms of the chromatic indexes of their constituent tones
let major : TChordType = {chordIndexes = [|0; 4; 7; 12|]; scaleType = Major}
let minor : TChordType = {chordIndexes = [|0; 3; 7; 12|]; scaleType = Minor}
let diminished : TChordType = {chordIndexes = [|0; 3; 6; 12|]; scaleType = Minor}
let augmented : TChordType = {chordIndexes = [|0; 5; 8; 12|]; scaleType = Major} // TODO check
let seventh : TChordType = {chordIndexes = major.chordIndexes @@ [|10|]; scaleType = Major}
let majorSeventh : TChordType = {chordIndexes = major.chordIndexes @@ [|11|]; scaleType = Major}
let minorSeventh : TChordType = {chordIndexes = minor.chordIndexes @@ [|10|]; scaleType = Minor}

/// Work out the human-readable note name for a particular chromatic index
let indexToName (index : int) (enharmonicPreference : TEnharmonicPreference) =
    allNotes
    |> Array.sortBy (fun item -> 
                            match enharmonicPreference with
                            | PreferFlat ->
                                            match item.accidental with
                                            | Flat -> 0
                                            | Natural -> 1
                                            | Sharp -> 2
                            | PreferSharp ->
                                            match item.accidental with
                                            | Sharp -> 0
                                            | Natural -> 1
                                            | Flat -> 2
                            | PreferNeither ->
                                            match item.accidental with
                                            | Natural -> 0
                                            | Flat -> 1
                                            | Sharp -> 2
                    )
    |> Array.find (fun item -> item.chromaticIndex = index)

/// Work out the chromatic index of a given note
let noteToIndex (note : TNote) =
    (note.octave * SEMITONES_PER_OCTAVE) + note.label.chromaticIndex

/// Work out into what octave a particular semitone falls (from an arbitrary lower basis)
let indexToOctave (index : int) =
    index / SEMITONES_PER_OCTAVE

/// Work out the human-readable note (including octave) for a particular semitone
let indexToNote (index : int) (enharmonicPreference : TEnharmonicPreference) =
    {label = indexToName (index % SEMITONES_PER_OCTAVE) enharmonicPreference; octave = indexToOctave index}

/// An operator to detect whether one note is the same as or is an enharmonic of another (ignoring octave)
let (=~) note1 note2 =
    note1.chromaticIndex = note2.chromaticIndex

/// As =~ but the compared notes must also be the same octave
let (==~) note1 note2 =
    (note1.label =~ note2.label)
    && (note1.octave = note2.octave)

/// Return a note which is n semitones higher than the input note
let addSemitones note semitones enharmonicPreference =
    let newIndex = noteToIndex(note) + semitones
    indexToNote newIndex enharmonicPreference 

/// Return the note which results from playing the specified string at the specified fret:
let frettingToNote (instrument : TInstrument) (fretting : TFretting) : TNote =
    let openNote = instrument.tuning.[fretting.stringIndex]
    let frettedNote = addSemitones openNote fretting.fretIndex PreferNeither
    frettedNote

/// Given the root note and scale type of a chord, work out whether any sharps/flats in the chord
/// should be expressed using the sharp or the flat of an enharmonic pair 
let rootNoteToEnharmonicPreference (rootNote : TNote) (scaleType : TScaleType) =
    match (rootNote.label.name, rootNote.label.accidental) with
        // TODO many of these need checking
        | ('A', Natural) -> 
            match scaleType with
                | Major -> PreferSharp
                | Minor -> PreferFlat
        | ('A', Sharp) -> 
            match scaleType with
                | Major -> PreferSharp
                | Minor -> PreferSharp
        | ('B', Flat) -> 
            match scaleType with
                | Major -> PreferFlat
                | Minor -> PreferFlat
        | ('B', Natural) -> 
            match scaleType with
                | Major -> PreferSharp
                | Minor -> PreferFlat
        | ('C', Natural) -> 
            match scaleType with
                | Major -> PreferSharp
                | Minor -> PreferFlat
        | ('C', Sharp) -> 
            match scaleType with
                | Major -> PreferSharp
                | Minor -> PreferSharp
        | ('D', Flat) -> 
            match scaleType with
                | Major -> PreferFlat
                | Minor -> PreferFlat
        | ('D', Natural) -> 
            match scaleType with
                | Major -> PreferSharp
                | Minor -> PreferFlat
        | ('D', Sharp) -> 
            match scaleType with
                | Major -> PreferSharp
                | Minor -> PreferSharp
        | ('E', Flat) -> 
            match scaleType with
                | Major -> PreferFlat
                | Minor -> PreferFlat
        | ('E', Natural) -> 
            match scaleType with
                | Major -> PreferSharp
                | Minor -> PreferFlat
        | ('F', Natural) -> 
            match scaleType with
                | Major -> PreferFlat
                | Minor -> PreferSharp
        | ('F', Sharp) -> 
            match scaleType with
                | Major -> PreferSharp
                | Minor -> PreferSharp
        | ('G', Flat) -> 
            match scaleType with
                | Major -> PreferFlat
                | Minor -> PreferFlat
        | ('G', Natural) -> 
            match scaleType with
                | Major -> PreferSharp
                | Minor -> PreferSharp
        | ('G', Sharp) -> 
            match scaleType with
                | Major -> PreferSharp
                | Minor -> PreferSharp
        | ('A', Flat) -> 
            match scaleType with
                | Major -> PreferFlat
                | Minor -> PreferFlat
        | _ -> failwith "rootNoteToEnharmonicPreference: Unexpected root note: %A" rootNote

/// Takes a root note and chord type and returns the actual notes of the chord:
let chordOf (rootNote : TNote) (chordType : TChordType) =
    chordType.chordIndexes
    |> Array.map (fun index -> addSemitones rootNote index (rootNoteToEnharmonicPreference rootNote chordType.scaleType) )

/// List all the notes you could play on a given string between a lowest and highest fret
let notesBetween (instrument : TInstrument) (stringIndex : int) (lowestFret : int) (highestFret : int) : seq<TFrettedNote> =
    let frettedNotes = 
        seq {
            for fret in lowestFret..highestFret do 
                let aFretting = {stringIndex = stringIndex; fretIndex = fret}
                let aNote = frettingToNote instrument aFretting
                yield {fretting = aFretting; note = aNote}
        } 
    frettedNotes

/// As notesBetween but also including the note produced by the same string played open
let notesBetweenAndOpen (instrument : TInstrument) (stringIndex : int) (lowestFret : int) (highestFret : int) : seq<TFrettedNote> =
    (notesBetween instrument stringIndex 0 0) |> Seq.append <| (notesBetween instrument stringIndex lowestFret highestFret)

/// List all the notes which could be played in a range of frets, including notes available by playing a string open
let notesInBox (instrument : TInstrument) (lowestFret : int) (highestFret : int) =
    [|0..(Array.length instrument.tuning)-1|]
    |> Array.map (fun stringIndex -> notesBetweenAndOpen instrument stringIndex lowestFret highestFret)

/// Given two sequences and a comparator function, find the pairs of items for which the comparator returns true
let findPairs compare seqT seqU =
    seq {
            for t in seqT do
                for u in seqU do
                    if (compare t u) then
                        yield (t, u)
    }

/// Given a two sequences and a comparator function, find the first pair of items for which the comparator returns true
let tryFindFirstPair compare seqT seqU =
    let matches = findPairs compare seqT seqU
    if not (Seq.isEmpty matches) then
        Some(Seq.nth 0 matches)
    else
        None

/// Reverse a sequence (don't use on infinite seq's!)
let reverseSeq s =
    s |> Array.ofSeq |> Array.rev |> Seq.ofArray

/// Like skipWhile, but skips items from the point where the function first returns false.
/// (Don't use on infinite seq's!)
let skipAfter f s =
    s
    |> reverseSeq
    |> Seq.skipWhile (fun elem -> f elem)
    |> reverseSeq

/// Print the frettings for a shape
let printShape (label : string) (shape : seq<TFrettedNote>) =
    printfn "%s" label
    shape
    |> Seq.iter (fun fretting -> printfn "String %i fret %i" (fretting.fretting.stringIndex+1) (fretting.fretting.fretIndex) )
    |> ignore

/// For a given chord, search through the notes which could be played within a given range of frets to try and
/// provide a set of frettings which plays the notes for the chord:
let findShape (instrument : TInstrument) (lowestFret : int) (highestFret : int) (chord : TChord) =
    // Create a map of required notes and how many times they have been found (initially all 0):
    let foundNotes = chord |> Array.map (fun note -> {mappedNote = note; useCount = 0})
    // A way to update the map to indicate that this note of the chord has been successfully provided:
    let markDone note =
        let mapIndex = foundNotes |> Array.findIndex (fun item -> item.mappedNote = note)
        foundNotes.[mapIndex].useCount <- foundNotes.[mapIndex].useCount + 1
    // Create a list of notes are needed in priority order, where priority is defined as
    // first, prioritise notes which haven't been found at all; and second, prioritise notes in low-to-high order:
    // (Defined as a function() so that when a note is marked as provided it goes to the back of the queue.)
    let notesInPriorityOrder() = 
        foundNotes 
        |> Array.sortBy (fun item -> (item.useCount*100) + item.mappedNote.label.chromaticIndex)
        |> Array.map (fun item -> item.mappedNote)
        |> Seq.ofArray
    // Go through the strings from low to high listing the notes that string could play:
    let frettings =
        seq {for availableNotesForString in (notesInBox instrument lowestFret highestFret) do
                // Search the available notes and the required notes (the latter in priority order) finding the first
                // instance (if any) on this string where the required note can be played. (Since we use the =~ this might be in
                // any octave.)
                let hit = tryFindFirstPair (fun availNote wantedNote -> availNote.note.label =~ wantedNote.label) 
                                                availableNotesForString (notesInPriorityOrder()) 
                // If we found a note:
                if hit <> None then 
                    // Flag that this note has been found:
                    markDone (snd(hit.Value))
                    // Yield the note together with its fretting:
                    yield fst(hit.Value) 
        }
    // We MUST have the root note at the bottom, so delete any frettings off the end of the sequence 
    // after the root note:
    let rootNote = chord.[0]
    frettings |> skipAfter (fun fretting -> not (fretting.note ==~ rootNote))

// Ordinary 6-string with EADGBE tuning:
let testGuitar = new TInstrument(
                                19, // Including nut
                                [|  // Treble side
                                    {label=ENat; octave=2}
                                    {label=BNat; octave=2}
                                    {label=GNat; octave=1}
                                    {label=DNat; octave=1}
                                    {label=ANat; octave=1}
                                    {label=ENat; octave=0}
                                    // Bass side
                                |]
                              )

// Some chords to play:
let CMaj = chordOf {label=CNat; octave=0} major
let DMaj = chordOf {label=DNat; octave=0} major
let DMin = chordOf {label=DNat; octave=0} minor
let D7 = chordOf {label=DNat; octave=0} seventh
let DMaj7 = chordOf {label=DNat; octave=0} majorSeventh
let EMaj = chordOf {label=ENat; octave=0} major
let EMin = chordOf {label=ENat; octave=0} minor
let AMaj = chordOf {label=ANat; octave=0} major
let AMin = chordOf {label=ANat; octave=0} minor
let ADim = chordOf {label=ANat; octave=0} diminished

// Generate fingerings for the chords:
findShape testGuitar 0 3 CMaj |> printShape "C Major" |> ignore
findShape testGuitar 0 3 EMaj |> printShape "E Major" |> ignore
findShape testGuitar 0 3 EMin |> printShape "E Minor" |> ignore
findShape testGuitar 0 3 AMaj |> printShape "A Major" |> ignore
findShape testGuitar 0 3 AMin |> printShape "A Minor" |> ignore
findShape testGuitar 0 3 ADim |> printShape "A Dim" |> ignore
findShape testGuitar 0 3 DMaj |> printShape "D Major" |> ignore
findShape testGuitar 0 3 DMin |> printShape "D Minor" |> ignore
findShape testGuitar 0 3 D7 |> printShape "D seventh" |> ignore
findShape testGuitar 0 3 DMaj7 |> printShape "D major seventh" |> ignore

// Output:
//  C Major
//  String 1 fret 0
//  String 2 fret 1
//  String 3 fret 0
//  String 4 fret 2
//  String 5 fret 3

// E Major
//  String 1 fret 0
//  String 2 fret 0
//  String 3 fret 1
//  String 4 fret 2
//  String 5 fret 2
//  String 6 fret 0

// E Minor
//  String 1 fret 0
//  String 2 fret 0
//  String 3 fret 0
//  String 4 fret 2
//  String 5 fret 2
//  String 6 fret 0

// D Major
//  String 1 fret 2
//  String 2 fret 3
//  String 3 fret 2
//  String 4 fret 0
val SEMITONES_PER_OCTAVE : int

Full name: Script.SEMITONES_PER_OCTAVE
type TAccidental =
  | Flat
  | Natural
  | Sharp

Full name: Script.TAccidental
union case TAccidental.Flat: TAccidental
union case TAccidental.Natural: TAccidental
union case TAccidental.Sharp: TAccidental
type TNoteLabel =
  {name: char;
   accidental: TAccidental;
   chromaticIndex: int;}

Full name: Script.TNoteLabel
TNoteLabel.name: char
Multiple items
val char : value:'T -> char (requires member op_Explicit)

Full name: Microsoft.FSharp.Core.Operators.char

--------------------
type char = System.Char

Full name: Microsoft.FSharp.Core.char
TNoteLabel.accidental: TAccidental
TNoteLabel.chromaticIndex: int
Multiple items
val int : value:'T -> int (requires member op_Explicit)

Full name: Microsoft.FSharp.Core.Operators.int

--------------------
type int = int32

Full name: Microsoft.FSharp.Core.int

--------------------
type int<'Measure> = int

Full name: Microsoft.FSharp.Core.int<_>
type TNote =
  {label: TNoteLabel;
   octave: int;}

Full name: Script.TNote
TNote.label: TNoteLabel
TNote.octave: int
type TChordIndexes = int array

Full name: Script.TChordIndexes
type 'T array = 'T []

Full name: Microsoft.FSharp.Core.array<_>
type TScaleType =
  | Major
  | Minor

Full name: Script.TScaleType
union case TScaleType.Major: TScaleType
union case TScaleType.Minor: TScaleType
type TChordType =
  {chordIndexes: TChordIndexes;
   scaleType: TScaleType;}

Full name: Script.TChordType
TChordType.chordIndexes: TChordIndexes
TChordType.scaleType: TScaleType
type TChord = TNote array

Full name: Script.TChord
type TEnharmonicPreference =
  | PreferFlat
  | PreferSharp
  | PreferNeither

Full name: Script.TEnharmonicPreference
union case TEnharmonicPreference.PreferFlat: TEnharmonicPreference
union case TEnharmonicPreference.PreferSharp: TEnharmonicPreference
union case TEnharmonicPreference.PreferNeither: TEnharmonicPreference
type TNoteMapping =
  {mappedNote: TNote;
   mutable useCount: int;}

Full name: Script.TNoteMapping
TNoteMapping.mappedNote: TNote
TNoteMapping.useCount: int
type TTuning = TNote array

Full name: Script.TTuning
type TFretting =
  {stringIndex: int;
   fretIndex: int;}

Full name: Script.TFretting
TFretting.stringIndex: int
TFretting.fretIndex: int
type TFrettedNote =
  {fretting: TFretting;
   note: TNote;}

Full name: Script.TFrettedNote
TFrettedNote.fretting: TFretting
TFrettedNote.note: TNote
Multiple items
type TInstrument =
  new : fretCount:int * tuning:TTuning -> TInstrument
  member fretCount : int
  member tuning : TTuning

Full name: Script.TInstrument


 Any fretted instrument:


--------------------
new : fretCount:int * tuning:TTuning -> TInstrument
val fretCount : int
val tuning : TTuning
val this : TInstrument
member TInstrument.fretCount : int

Full name: Script.TInstrument.fretCount
member TInstrument.tuning : TTuning

Full name: Script.TInstrument.tuning
val allNotes : TNoteLabel []

Full name: Script.allNotes


 All human readable note names, including enharmonics (but not bothering with double-flats, double-sharps):
val ANat : TNoteLabel

Full name: Script.ANat


 Some useful constants for notes:
val ASharp : TNoteLabel

Full name: Script.ASharp
val BFlat : TNoteLabel

Full name: Script.BFlat
val BNat : TNoteLabel

Full name: Script.BNat
val BSharp : TNoteLabel

Full name: Script.BSharp
val CFlat : TNoteLabel

Full name: Script.CFlat
val CNat : TNoteLabel

Full name: Script.CNat
val CSharp : TNoteLabel

Full name: Script.CSharp
val DFlat : TNoteLabel

Full name: Script.DFlat
val DNat : TNoteLabel

Full name: Script.DNat
val DSharp : TNoteLabel

Full name: Script.DSharp
val EFlat : TNoteLabel

Full name: Script.EFlat
val ENat : TNoteLabel

Full name: Script.ENat
val ESharp : TNoteLabel

Full name: Script.ESharp
val FFlat : TNoteLabel

Full name: Script.FFlat
val FNat : TNoteLabel

Full name: Script.FNat
Multiple items
val FSharp : TNoteLabel

Full name: Script.FSharp

--------------------
namespace Microsoft.FSharp
val GFlat : TNoteLabel

Full name: Script.GFlat
val GNat : TNoteLabel

Full name: Script.GNat
val GSharp : TNoteLabel

Full name: Script.GSharp
val AFlat : TNoteLabel

Full name: Script.AFlat
val a : 'a []
val b : 'a []
module Array

from Microsoft.FSharp.Collections
val concat : arrays:seq<'T []> -> 'T []

Full name: Microsoft.FSharp.Collections.Array.concat
val major : TChordType

Full name: Script.major
val minor : TChordType

Full name: Script.minor
val diminished : TChordType

Full name: Script.diminished
val augmented : TChordType

Full name: Script.augmented
val seventh : TChordType

Full name: Script.seventh
val majorSeventh : TChordType

Full name: Script.majorSeventh
val minorSeventh : TChordType

Full name: Script.minorSeventh
val indexToName : index:int -> enharmonicPreference:TEnharmonicPreference -> TNoteLabel

Full name: Script.indexToName


 Work out the human-readable note name for a particular chromatic index
val index : int
val enharmonicPreference : TEnharmonicPreference
val sortBy : projection:('T -> 'Key) -> array:'T [] -> 'T [] (requires comparison)

Full name: Microsoft.FSharp.Collections.Array.sortBy
val item : TNoteLabel
val find : predicate:('T -> bool) -> array:'T [] -> 'T

Full name: Microsoft.FSharp.Collections.Array.find
val noteToIndex : note:TNote -> int

Full name: Script.noteToIndex


 Work out the chromatic index of a given note
val note : TNote
val indexToOctave : index:int -> int

Full name: Script.indexToOctave


 Work out into what octave a particular semitone falls (from an arbitrary lower basis)
val indexToNote : index:int -> enharmonicPreference:TEnharmonicPreference -> TNote

Full name: Script.indexToNote


 Work out the human-readable note (including octave) for a particular semitone
val note1 : TNoteLabel
val note2 : TNoteLabel
val note1 : TNote
val note2 : TNote
val addSemitones : note:TNote -> semitones:int -> enharmonicPreference:TEnharmonicPreference -> TNote

Full name: Script.addSemitones


 Return a note which is n semitones higher than the input note
val semitones : int
val newIndex : int
val frettingToNote : instrument:TInstrument -> fretting:TFretting -> TNote

Full name: Script.frettingToNote


 Return the note which results from playing the specified string at the specified fret:
val instrument : TInstrument
val fretting : TFretting
val openNote : TNote
property TInstrument.tuning: TTuning
val frettedNote : TNote
val rootNoteToEnharmonicPreference : rootNote:TNote -> scaleType:TScaleType -> TEnharmonicPreference

Full name: Script.rootNoteToEnharmonicPreference


 Given the root note and scale type of a chord, work out whether any sharps/flats in the chord
 should be expressed using the sharp or the flat of an enharmonic pair
val rootNote : TNote
val scaleType : TScaleType
val failwith : message:string -> 'T

Full name: Microsoft.FSharp.Core.Operators.failwith
val chordOf : rootNote:TNote -> chordType:TChordType -> TNote []

Full name: Script.chordOf


 Takes a root note and chord type and returns the actual notes of the chord:
val chordType : TChordType
val map : mapping:('T -> 'U) -> array:'T [] -> 'U []

Full name: Microsoft.FSharp.Collections.Array.map
val notesBetween : instrument:TInstrument -> stringIndex:int -> lowestFret:int -> highestFret:int -> seq<TFrettedNote>

Full name: Script.notesBetween


 List all the notes you could play on a given string between a lowest and highest fret
val stringIndex : int
val lowestFret : int
val highestFret : int
Multiple items
val seq : sequence:seq<'T> -> seq<'T>

Full name: Microsoft.FSharp.Core.Operators.seq

--------------------
type seq<'T> = System.Collections.Generic.IEnumerable<'T>

Full name: Microsoft.FSharp.Collections.seq<_>
val frettedNotes : seq<TFrettedNote>
val fret : int
val aFretting : TFretting
val aNote : TNote
val notesBetweenAndOpen : instrument:TInstrument -> stringIndex:int -> lowestFret:int -> highestFret:int -> seq<TFrettedNote>

Full name: Script.notesBetweenAndOpen


 As notesBetween but also including the note produced by the same string played open
module Seq

from Microsoft.FSharp.Collections
val append : source1:seq<'T> -> source2:seq<'T> -> seq<'T>

Full name: Microsoft.FSharp.Collections.Seq.append
val notesInBox : instrument:TInstrument -> lowestFret:int -> highestFret:int -> seq<TFrettedNote> []

Full name: Script.notesInBox


 List all the notes which could be played in a range of frets, including notes available by playing a string open
val length : array:'T [] -> int

Full name: Microsoft.FSharp.Collections.Array.length
val findPairs : compare:('a -> 'b -> bool) -> seqT:seq<'a> -> seqU:seq<'b> -> seq<'a * 'b>

Full name: Script.findPairs


 Given two sequences and a comparator function, find the pairs of items for which the comparator returns true
val compare : ('a -> 'b -> bool)
val seqT : seq<'a>
val seqU : seq<'b>
val t : 'a
val u : 'b
val tryFindFirstPair : compare:('a -> 'b -> bool) -> seqT:seq<'a> -> seqU:seq<'b> -> ('a * 'b) option

Full name: Script.tryFindFirstPair


 Given a two sequences and a comparator function, find the first pair of items for which the comparator returns true
val matches : seq<'a * 'b>
val not : value:bool -> bool

Full name: Microsoft.FSharp.Core.Operators.not
val isEmpty : source:seq<'T> -> bool

Full name: Microsoft.FSharp.Collections.Seq.isEmpty
union case Option.Some: Value: 'T -> Option<'T>
val nth : index:int -> source:seq<'T> -> 'T

Full name: Microsoft.FSharp.Collections.Seq.nth
union case Option.None: Option<'T>
val reverseSeq : s:seq<'a> -> seq<'a>

Full name: Script.reverseSeq


 Reverse a sequence (don't use on infinite seq's!)
val s : seq<'a>
val ofSeq : source:seq<'T> -> 'T []

Full name: Microsoft.FSharp.Collections.Array.ofSeq
val rev : array:'T [] -> 'T []

Full name: Microsoft.FSharp.Collections.Array.rev
val ofArray : source:'T [] -> seq<'T>

Full name: Microsoft.FSharp.Collections.Seq.ofArray
val skipAfter : f:('a -> bool) -> s:seq<'a> -> seq<'a>

Full name: Script.skipAfter


 Like skipWhile, but skips items from the point where the function first returns false.
 (Don't use on infinite seq's!)
val f : ('a -> bool)
val skipWhile : predicate:('T -> bool) -> source:seq<'T> -> seq<'T>

Full name: Microsoft.FSharp.Collections.Seq.skipWhile
val elem : 'a
val printShape : label:string -> shape:seq<TFrettedNote> -> unit

Full name: Script.printShape


 Print the frettings for a shape
val label : string
Multiple items
val string : value:'T -> string

Full name: Microsoft.FSharp.Core.Operators.string

--------------------
type string = System.String

Full name: Microsoft.FSharp.Core.string
val shape : seq<TFrettedNote>
val printfn : format:Printf.TextWriterFormat<'T> -> 'T

Full name: Microsoft.FSharp.Core.ExtraTopLevelOperators.printfn
val iter : action:('T -> unit) -> source:seq<'T> -> unit

Full name: Microsoft.FSharp.Collections.Seq.iter
val fretting : TFrettedNote
val ignore : value:'T -> unit

Full name: Microsoft.FSharp.Core.Operators.ignore
val findShape : instrument:TInstrument -> lowestFret:int -> highestFret:int -> chord:TChord -> seq<TFrettedNote>

Full name: Script.findShape


 For a given chord, search through the notes which could be played within a given range of frets to try and
 provide a set of frettings which plays the notes for the chord:
val chord : TChord
val foundNotes : TNoteMapping []
val markDone : (TNote -> unit)
val mapIndex : int
val findIndex : predicate:('T -> bool) -> array:'T [] -> int

Full name: Microsoft.FSharp.Collections.Array.findIndex
val item : TNoteMapping
val notesInPriorityOrder : (unit -> seq<TNote>)
val frettings : seq<TFrettedNote>
val availableNotesForString : seq<TFrettedNote>
val hit : (TFrettedNote * TNote) option
val availNote : TFrettedNote
val wantedNote : TNote
val snd : tuple:('T1 * 'T2) -> 'T2

Full name: Microsoft.FSharp.Core.Operators.snd
property Option.Value: TFrettedNote * TNote
val fst : tuple:('T1 * 'T2) -> 'T1

Full name: Microsoft.FSharp.Core.Operators.fst
val testGuitar : TInstrument

Full name: Script.testGuitar
val CMaj : TNote []

Full name: Script.CMaj
val DMaj : TNote []

Full name: Script.DMaj
val DMin : TNote []

Full name: Script.DMin
val D7 : TNote []

Full name: Script.D7
val DMaj7 : TNote []

Full name: Script.DMaj7
val EMaj : TNote []

Full name: Script.EMaj
val EMin : TNote []

Full name: Script.EMin
val AMaj : TNote []

Full name: Script.AMaj
val AMin : TNote []

Full name: Script.AMin
val ADim : TNote []

Full name: Script.ADim

More information

Link:http://fssnip.net/76
Posted:12 years ago
Author:Kit Eason
Tags: guitar , chord , music