arca-0.1.0.0: A digital implementation of Athanasius Kircher's device for automatic music composition, the Arca musarithmica of 1650

Copyright(c) 2022 Andrew A. Cashner
StabilityExperimental
Safe HaskellNone
LanguageHaskell2010

Aedifico

Contents

Description

This module provides the data structures and methods for storing the data of Kircher's ark and then extracting it. (*aedifico* = Latin, "I build") The Arca_musarithmica module actually builds it.

Kircher's specification

As described in Kircher's Musurgia universalis (Rome, 1650), book 8, the ark is a box containing rods (pinakes), each of which includes columns with voice and rhythm permutations. The rods are grouped according to style into syntagmata, where syntagma 1 is simple homorhythmic counterpoint. There are two surviving exemplars of physical implementations of the ark.

The top part of Kircher's "rods" contain tables table of numbers with four rows, where the numbers represent pitch offsets from a modal base note, and the rows are the notes for the four voice parts SATB. Each table represents the notes to set a single phrase of text with a given number of syllables.

Implementation

This module implements analogous data structures using Haskell types and defines methods for building the ark from input data, and for accessing each element of the ark data.

It also defines the data types needed for the other modules.

Structure of the ark in Haskell implementation (simplified)

   Arca
       vperms
           Arca                     = Vector (Syntagma)
           Syntagma                 = Vector (Pinax)
           Pinax                    = Vector (Column)
           Column { colVpermTable } = VpermTable
           VpermTable { vperms }    = Vector (VpermChoir)
           VpermChoir               = Vector (Vperm)
           Vperm                    = [Int]

       rperms
           Arca                     = Vector (Syntagma)
           Syntagma                 = Vector (Pinax)
           Pinax                    = Vector (Column)
           Column { colRpermTable } = RpermTable
           RpermTable               = Vector (RpermMeter)
           RpermMeter { rperms }    = Vector (RpermChoir)
           RpermChoir               = Vector (Rperm)
           Rperm                    = [Dur]

Accessing perms directly

The test module Spec.hs shows how to access all of the ark data directly. These notes might clarify how to reach individual ark vperms or rperms.

      vperms
           perms arca          :: Vector (Vector (Vector Column))
           colVpermTable       :: VpermTable
           vperms vpermTable   :: Vector (Vector [Int])

           vperm :: [Int]
           vperm = vperms table ! vpermIndex ! voiceIndex
           where
               table  = colVpermTable $ column ! columnIndex
               column = perms arca ! syntagmaIndex ! pinaxIndex ! columnIndex

      rperms
           rperm :: [Dur]
           rperm = rperms table ! rpermMeterIndex ! rpermVoiceIndex
           where
               table  = colVpermTable $ column ! columnIndex
               column = perms arca ! syntagmaIndex ! pinaxIndex ! columnIndex
Synopsis

Utitilies

(!!?) :: [a] -> Int -> Maybe a Source #

Safe list indexing

Data types

Equivalents of Kircher's Rods and Tables

data Pnum Source #

Pitches

The Pnum is a 0-indexed diatonic pitch-class number, C through C an octave higher. (In Kircher's 1-indexed system he uses both 1 and 8 for C so we must be able to tell the difference.)

Constructors

PCc 
PCd 
PCe 
PCf 
PCg 
PCa 
PCb 
PCc8

C an octave higher

Rest 
Instances
Enum Pnum Source # 
Instance details

Defined in Aedifico

Methods

succ :: Pnum -> Pnum #

pred :: Pnum -> Pnum #

toEnum :: Int -> Pnum #

fromEnum :: Pnum -> Int #

enumFrom :: Pnum -> [Pnum] #

enumFromThen :: Pnum -> Pnum -> [Pnum] #

enumFromTo :: Pnum -> Pnum -> [Pnum] #

enumFromThenTo :: Pnum -> Pnum -> Pnum -> [Pnum] #

Eq Pnum Source # 
Instance details

Defined in Aedifico

Methods

(==) :: Pnum -> Pnum -> Bool #

(/=) :: Pnum -> Pnum -> Bool #

Ord Pnum Source # 
Instance details

Defined in Aedifico

Methods

compare :: Pnum -> Pnum -> Ordering #

(<) :: Pnum -> Pnum -> Bool #

(<=) :: Pnum -> Pnum -> Bool #

(>) :: Pnum -> Pnum -> Bool #

(>=) :: Pnum -> Pnum -> Bool #

max :: Pnum -> Pnum -> Pnum #

min :: Pnum -> Pnum -> Pnum #

Show Pnum Source # 
Instance details

Defined in Aedifico

Methods

showsPrec :: Int -> Pnum -> ShowS #

show :: Pnum -> String #

showList :: [Pnum] -> ShowS #

toPnum :: Int -> Pnum Source #

Convert any integer to a Pnum

data Accid Source #

Accidentals

Constructors

Fl

flat

Na

natural

Sh

sharp

AccidNil

when note is a rest

Instances
Enum Accid Source # 
Instance details

Defined in Aedifico

Eq Accid Source # 
Instance details

Defined in Aedifico

Methods

(==) :: Accid -> Accid -> Bool #

(/=) :: Accid -> Accid -> Bool #

Ord Accid Source # 
Instance details

Defined in Aedifico

Methods

compare :: Accid -> Accid -> Ordering #

(<) :: Accid -> Accid -> Bool #

(<=) :: Accid -> Accid -> Bool #

(>) :: Accid -> Accid -> Bool #

(>=) :: Accid -> Accid -> Bool #

max :: Accid -> Accid -> Accid #

min :: Accid -> Accid -> Accid #

Show Accid Source # 
Instance details

Defined in Aedifico

Methods

showsPrec :: Int -> Accid -> ShowS #

show :: Accid -> String #

showList :: [Accid] -> ShowS #

data Octave Source #

Octaves

We set octave numbers in the Helmholtz system (middle C = C4); we only need the enum OctNil if the note is a rest.

TODO check

Constructors

OctNil 
Instances
Enum Octave Source # 
Instance details

Defined in Aedifico

Eq Octave Source # 
Instance details

Defined in Aedifico

Methods

(==) :: Octave -> Octave -> Bool #

(/=) :: Octave -> Octave -> Bool #

Ord Octave Source # 
Instance details

Defined in Aedifico

Show Octave Source # 
Instance details

Defined in Aedifico

data VoiceName Source #

Voices

The ark always produces four-voice polyphony.

Constructors

Cantus 
Alto 
Tenor 
Bass 

data VoiceRange Source #

Vocal Ranges

Constructors

VoiceRange 

Fields

data Dur Source #

Duration values

We use the mensural names; first the base values, then dotted variants, then a series marked as rest values.

Constructors

DurNil

unset

Lg

longa

Br

breve

Sb

semibreve

Mn

minim

Sm

semiminim

Fs

fusa

LgD

dotted longa

BrD

dotted breve

SbD

dotted semibreve

MnD

dotted minim

SmD

dotted semiminim

FsD

dotted fusa

LgR

longa rest

BrR

breve rest

SbR

semibreve rest

MnR

minim rest

SmR

semiminim rest

FsR

fusa rest

Instances
Enum Dur Source # 
Instance details

Defined in Aedifico

Methods

succ :: Dur -> Dur #

pred :: Dur -> Dur #

toEnum :: Int -> Dur #

fromEnum :: Dur -> Int #

enumFrom :: Dur -> [Dur] #

enumFromThen :: Dur -> Dur -> [Dur] #

enumFromTo :: Dur -> Dur -> [Dur] #

enumFromThenTo :: Dur -> Dur -> Dur -> [Dur] #

Eq Dur Source # 
Instance details

Defined in Aedifico

Methods

(==) :: Dur -> Dur -> Bool #

(/=) :: Dur -> Dur -> Bool #

Ord Dur Source # 
Instance details

Defined in Aedifico

Methods

compare :: Dur -> Dur -> Ordering #

(<) :: Dur -> Dur -> Bool #

(<=) :: Dur -> Dur -> Bool #

(>) :: Dur -> Dur -> Bool #

(>=) :: Dur -> Dur -> Bool #

max :: Dur -> Dur -> Dur #

min :: Dur -> Dur -> Dur #

Show Dur Source # 
Instance details

Defined in Aedifico

Methods

showsPrec :: Int -> Dur -> ShowS #

show :: Dur -> String #

showList :: [Dur] -> ShowS #

data AccidType Source #

How should the accidental be displayed? (Needed for MEI)

Constructors

None

No accidental

Written

MEI accid

Implicit

MEI accid.ges

Suggested

MEI accid + func="edit"

Instances
Eq AccidType Source # 
Instance details

Defined in Aedifico

Ord AccidType Source # 
Instance details

Defined in Aedifico

Show AccidType Source # 
Instance details

Defined in Aedifico

data Pitch Source #

A Pitch stores the essential information for notating a single note.

Constructors

Pitch 

Fields

Instances
Eq Pitch Source # 
Instance details

Defined in Aedifico

Methods

(==) :: Pitch -> Pitch -> Bool #

(/=) :: Pitch -> Pitch -> Bool #

Ord Pitch Source # 
Instance details

Defined in Aedifico

Methods

compare :: Pitch -> Pitch -> Ordering #

(<) :: Pitch -> Pitch -> Bool #

(<=) :: Pitch -> Pitch -> Bool #

(>) :: Pitch -> Pitch -> Bool #

(>=) :: Pitch -> Pitch -> Bool #

max :: Pitch -> Pitch -> Pitch #

min :: Pitch -> Pitch -> Pitch #

Show Pitch Source # 
Instance details

Defined in Aedifico

Methods

showsPrec :: Int -> Pitch -> ShowS #

show :: Pitch -> String #

showList :: [Pitch] -> ShowS #

simplePitch Source #

Arguments

:: (Pnum, Int)

Pitch enum and Helmholtz octave number

-> Pitch 

Make a pitch with only pnum and octave, no duration or accidental

Metrical Systems

data MusicMeter Source #

Kircher only seems to allow for duple (not making distinction between C and cut C), cut C 3 (triple major) and C3 (triple minor).

TODO Should we distinguish between C and cut C duple?

Constructors

Duple 
TripleMajor 
TripleMinor 

toMusicMeter :: String -> MusicMeter Source #

Select meter by string

Textual/poetic meter

data TextMeter Source #

Text meter (of input text, distinguished from musical meter of setting)

Constructors

TextMeterNil 
Prose

No meter, free, or irregular

ProseLong

Prose, 2-6 syllabels, penultimate is long

ProseShort

Prose, 2-6 syllables, penultimate is short

Adonium

5 syllables (`--`-)

Dactylicum

6 syllables (`--`--)

IambicumEuripidaeum

6 syllables (--`-)

Anacreonticum

7 syllables, penultimate long

IambicumArchilochicum

8 syllables, penultimate short

IambicumEnneasyllabicum

9 syllables, penultimate long

Enneasyllabicum

9 syllables (generic)

Decasyllabicum

10 syllables, penultimate short

PhaleuciumHendecasyllabicum

11 syllables

Hendecasyllabicum

11 syllables (generic)

Sapphicum

11 syllables, three lines + 5-syllable tag

Dodecasyllabicum

12 syllables, penultimate short

toTextMeter :: String -> TextMeter Source #

Select text meter by string

maxSyllables :: TextMeter -> Int Source #

Get maximum number of syllables for a TextMeter

Style

data Style Source #

The choice of style determines which of Kircher's three syntagmata we select. Simple style calls up Syntagma 1 for simple, note-against-note (first-species) homorhythmic counterpoint. Florid style calls up Syntagma 2 for syllabic, imitative, and even in some permutations fugal counterpoint.

TODO There is also a third syntagma, for adding rhetorical figures to simple counterpoint for more nuanced text-setting. We have not yet implemented this, and do not know if it can be fully automated.

Constructors

Simple

Syllabic, homorhythmic counterpoint (syntagma 1)

Florid

Melismatic, imitative counterpoint (syntagma 2)

Instances
Enum Style Source # 
Instance details

Defined in Aedifico

Eq Style Source # 
Instance details

Defined in Aedifico

Methods

(==) :: Style -> Style -> Bool #

(/=) :: Style -> Style -> Bool #

Ord Style Source # 
Instance details

Defined in Aedifico

Methods

compare :: Style -> Style -> Ordering #

(<) :: Style -> Style -> Bool #

(<=) :: Style -> Style -> Bool #

(>) :: Style -> Style -> Bool #

(>=) :: Style -> Style -> Bool #

max :: Style -> Style -> Style #

min :: Style -> Style -> Style #

Show Style Source # 
Instance details

Defined in Aedifico

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

toStyle Source #

Arguments

:: String

Simple or Florid

-> Style 

Select style by string (used in processing XML input)

data Tone Source #

Tone

Kircher's table of tones is a hybrid of toni ecclesiastici or "church keys" which were matched to the eight traditional psalm tones in Gregorian chant, and the twelve modes of Zarlino.

Instances
Enum Tone Source # 
Instance details

Defined in Aedifico

Methods

succ :: Tone -> Tone #

pred :: Tone -> Tone #

toEnum :: Int -> Tone #

fromEnum :: Tone -> Int #

enumFrom :: Tone -> [Tone] #

enumFromThen :: Tone -> Tone -> [Tone] #

enumFromTo :: Tone -> Tone -> [Tone] #

enumFromThenTo :: Tone -> Tone -> Tone -> [Tone] #

Eq Tone Source # 
Instance details

Defined in Aedifico

Methods

(==) :: Tone -> Tone -> Bool #

(/=) :: Tone -> Tone -> Bool #

Ord Tone Source # 
Instance details

Defined in Aedifico

Methods

compare :: Tone -> Tone -> Ordering #

(<) :: Tone -> Tone -> Bool #

(<=) :: Tone -> Tone -> Bool #

(>) :: Tone -> Tone -> Bool #

(>=) :: Tone -> Tone -> Bool #

max :: Tone -> Tone -> Tone #

min :: Tone -> Tone -> Tone #

Show Tone Source # 
Instance details

Defined in Aedifico

Methods

showsPrec :: Int -> Tone -> ShowS #

show :: Tone -> String #

showList :: [Tone] -> ShowS #

toTone :: String -> Tone Source #

Select tone by string (e.g., Tone1 or Tone12 in XML input)

Kircher's table with the tone systems and tone notes, on the lid of the

data System Source #

Tone system, durus (natural) or mollis (one flat in the key signature)

Constructors

Durus 
Mollis 
Instances
Enum System Source # 
Instance details

Defined in Aedifico

Eq System Source # 
Instance details

Defined in Aedifico

Methods

(==) :: System -> System -> Bool #

(/=) :: System -> System -> Bool #

Ord System Source # 
Instance details

Defined in Aedifico

type ToneSystem = Vector System Source #

The series of System values for the tones

type PnumAccid = (Pnum, Accid) Source #

Combination Pnum and Accid used to set a Pitch

type ToneList = Vector (Vector PnumAccid) Source #

A list of scales, including some notes with accidentals, from Kircher

type PinaxLegalTones = AssocList PinaxLabel [[Tone]] Source #

List of tones appropriate for a single pinax

type PinaxToneList = AssocList Style PinaxLegalTones Source #

List of tones appropriate for each pinax within each syntagma (style): association list mapping style to sets of pinakes, and then pinakes to tones

assocLookup :: Eq a => a -> AssocList a b -> String -> b Source #

Lookup a value by equality in an association list, or raise an error if not found

tonesPerStyle :: Style -> PinaxLabel -> PinaxToneList -> [[Tone]] Source #

Get a list of legal tones for a given Style and PinaxLabel

data PenultLength Source #

Penultimate Syllable Length

Every unit of text to be set to music must be marked with either a long or short penultimate syllable.

Constructors

Long 
Short 

arca2pinax :: Arca -> Style -> PinaxLabel -> Pinax Source #

Extract a Pinax from the ark by style and pinax label

meter2pinax :: Style -> TextMeter -> PinaxLabel Source #

Get pinax from textual meter; this depends on the Style because the syntagmata differ in the order of meters, so IambicumEuripidaeum meter in Syntagma 1 is Pinax4, but in Syntagma 2 it is Pinax2.

isToneLegalInPinax Source #

Arguments

:: PinaxToneList

list of appropriate tones per pinax

-> Style

corresponding to syntagma

-> PinaxLabel

pinax enum within syntagma

-> Int

0-indexed line number (Kircher's "stropha")

-> Tone

tone enum to check

-> Bool 

Is this tone acceptable to use for this pinax in this syntagma, for this line number ("stropha")?

proseMeter :: PenultLength -> TextMeter Source #

In prose, determine TextMeter based on penultimate syllable length

data ArkConfig Source #

All the ark settings in one structure: We use this to pass configuration settings through many functions down to the core level of pulling data from the ark.

Constructors

ArkConfig 

Fields

Instances
Eq ArkConfig Source # 
Instance details

Defined in Aedifico

Ord ArkConfig Source # 
Instance details

Defined in Aedifico

Show ArkConfig Source # 
Instance details

Defined in Aedifico

Elements of the ark

Vperm: Pitch combinations for four-voice choir

type Vperm = [Int] Source #

The top part of Kircher's "rods" contain tables table of numbers with four rows, where the numbers represent pitch offsets from a modal base note, and the rows are the notes for the four voice parts SATB. Each table represents the notes to set a single phrase of text with a given number of syllables.

We implement the notes for one voice as a Vperm, a list of Int values.

type VpermChoir = Vector Vperm Source #

A vector of four Vperms makes a VpermChoir.

data VpermTable Source #

A Vector of VpermChoirs is a VpermTable, which represents the top part of Kircher's "rods". We need to know the vector length because it varies in different pinakes.

Constructors

VpermTable 

Fields

Rperm: Rhythm permutations to match the Vperm

type Rperm = [Dur] Source #

The bottom part of the "rods" contain tables of rhythmic values written with musical notes. In the simple note-against-note style, there is one list of values to match each table of voices.

We implement this using our Dur data type for the rhythmic values. An Rperm is a list of Dur values.

type RpermChoir = Vector Rperm Source #

In Syntagma I, there is only one set of rhythmic permutation that we apply to all four voices of the VpermChoir. But in Syntagma II, there are groups of four Rperms that match up with the four voices. So we make a "choir" as a vector of Rperms, though in Syntagma I this will always just have a single member.

data RpermMeter Source #

An RpermMeter includes a vector of RpermChoirs all in one meter (see the MusicMeter data type above) and the length of that vector.

Kircher has a variable number of Rperms in the different meters, in each column, so we need to know how many there are.

In Syntagma II everything is duple meter so there is just the one meter.

Constructors

RpermMeter 

Fields

type RpermTable = Vector RpermMeter Source #

The RpermTable is a vector containing all the rhythmic permutations for one of Kircher's "rods".

Assembling the data into Kircher's structures

data Column Source #

The ark is a box containing rods (pinakes), each of which includes columns with voice and rhythm permutations. The rods are grouped according to style into syntagmata, where syntagma 1 is simple homorhythmic counterpoint.

We implement the Column as a structure with one VpermTable and one RpermTable.

type Pinax = Vector Column Source #

A vector of Column instances is a Pinax.

type Syntagma = Vector Pinax Source #

A vector of Pinax instances is a Syntagma.

data Arca Source #

A vector of Syntagma instances plus the other elements of the physical device (tone table, vocal ranges, information matching tones to pinakes) makes up the full Arca.

Accessing the Data

By index

getVectorItem Source #

Arguments

:: String

name of calling function, for debugging

-> Vector a

vector to pull from

-> Int

index to select

-> a 

Just get a vector value by index, safely (combining fromJust and !?)

column Source #

Arguments

:: Arca

ark (there's only one, but someone could make more)

-> Style

style label for syntagma

-> PinaxLabel

pinax label

-> Int

column number

-> Column 

Getting a Column requires indexing through nested vectors. But because there are two parts of pinax 3 in syntagma 1, we can't just use the pinax label as an enum; we have to look up the number with arca2pinax.

vperm Source #

Arguments

:: Column 
-> Int

Index of voice permutation within the column

-> VpermChoir 

Getting a VpermChoir means taking the first of the Column 2-tuple; we select which one using a random number (from Fortuna module), though the Inquisition forbids chance operations

rperm Source #

Arguments

:: Column 
-> MusicMeter 
-> Int

Index of rhythm permutation

-> RpermChoir 

Getting an RpermChoir means taking data from Column, using the meter and a random index (for Kircher, user's choice)

By meaningful data

getVperm Source #

Arguments

:: Arca 
-> ArkConfig

we need Style

-> Int

syllable count

-> Int

line count

-> Int

(random) index

-> VpermChoir 

The user of Kircher's arca needs only to know the number of syllables in a phrase and whether the penultimate syllable is long or short. Then they must freely (?) choose which table in the column.

We go straight to a voice and a rhythm permutation, given all the needed variables and an index. Instead of choosing freely we tempt fate and use a random number.

toneOrToneB Source #

Arguments

:: ArkConfig 
-> Int

line number, zero indexed

-> Tone 

Use toneB attribute if needed, otherwise tone (We only use toneB for florid pinax 4, every third and fourth line!)

getRperm Source #

Arguments

:: Arca 
-> ArkConfig

we need Style and MusicMeter

-> Int

syllable count

-> Int

line count

-> Int

(random) index

-> RpermChoir 

Select the rhythm values for a single phrase from the ark's rhythm permutations (Rperms).

In Pinax 9, there is no TripleMinor category of rperms, so we screen that out first.

TODO: Using an error, but we could just substitute TripleMajor with a note in the log (if we had a log).

columnIndex Source #

Arguments

:: Style 
-> TextMeter 
-> Int

syllable count

-> Int

line count

-> Int 

The rule for selecting the column index varies depending on the pinax. Pinax 1 and 2 are determined by whether the penultimate syllables is long or short, respectively, and then the column is based on the number of syllables in the phrase.

For the other pinaces we are supposed to choose successive columns for each "stropha" (verse line), so here we select based on the position within a quatrain.

(TODO Kircher doesn't provide clear guidance about how to deal with poetry that cannot or should not be grouped in quatrains, and neither do we.)

There are different rules for each syntagma, hence the need for Style input.

getVoice Source #

Arguments

:: Arca 
-> ArkConfig

we pass this along to getVperm

-> Int

syllable count

-> Int

line count

-> VoiceName 
-> Int

(random) index

-> Vperm 

Select the pitch numbers for a single voice from one of the ark's pitch permutations (Vperms).

Building the Ark

Data structures for input to build the ark

type VpermTableInput = [[Vperm]] Source #

Voice permutation data: 1-indexed pitch numbers, sets of four voices each, usually ten sets per column

type RpermTableInput = [[[Rperm]]] Source #

Rhythm permutation data: Dur values, three sets for different meters, each containing either one set per voice permutation set (syntagma I) or a four-voice set to match (syntagma II)

type ColumnInput = (VpermTableInput, RpermTableInput) Source #

Column data: Pairs of input data for voice and rhythm permutations

type PinaxInput = [ColumnInput] Source #

Pinax data: List of data for columns

Transforming input data to ark structures

fromList2D :: [[a]] -> Vector (Vector a) Source #

To build the ark from the data in the Arca/ directory, we must take a singly nested list and make it into a vector of vectors. This allows for the data to be input and maintained more simply, as a nested list of integers and strings, but then converted to vectors for better performance. The innermost layer stays in list format.

TODO: Optimize?

buildVpermTable :: VpermTableInput -> VpermTable Source #

Make a new VpermTable that knows its own length: Application of fromList2D to Vperm

newRpermMeter :: [[Rperm]] -> RpermMeter Source #

Make a new RpermMeter that knows its own length.

buildRpermTable :: RpermTableInput -> RpermTable Source #

Build an RpermTable with RpermMeters that know their length.

buildColumn :: ColumnInput -> Column Source #

Build a Column directly from input data: two nested lists, one for all the voice permutations in the column and the other for all the rhythm permutations. Because we are manually entering Kircher's data for the ark we do not check for validity here, and there are several variations across the syntagmata and pinakes in how the data is structured.

buildPinax :: PinaxInput -> Pinax Source #

Build a Pinax from pairs of VpermTable and RpermTable data

buildSyntagma :: [Pinax] -> Syntagma Source #

Build a Syntagma from constructed Pinax items (not from raw input)

Pull out values simply for testing

columnFromArca Source #

Arguments

:: Arca 
-> Int

syntagma index

-> Int

pinax index

-> Int

column index

-> Column 

Pull out a single Column given indices

vpermFromArca Source #

Arguments

:: Arca 
-> Int

syntagma index

-> Int

pinax index

-> Int

column index

-> Int

vperm (row) index

-> Int

voice (SATB) index

-> Vperm 

Pull out a single Vperm, which is a list of Int

rpermFromArca Source #

Arguments

:: Arca 
-> Int

syntagma index

-> Int

pinax index

-> Int

column index

-> Int

meter index

-> Int

rperm index

-> Int

voice index

-> Rperm 

Pull out a single Rperm, which is a list of Dur