RiugaBachi / necrophagy

A type-level, statically-verified Haskell embedded domain specific language (EDSL) for writing guitar tablature.
BSD 3-Clause "New" or "Revised" License
24 stars 0 forks source link

necrophagy

  1. (n) The eating of dead or decaying animal flesh
  2. (n) Feeding on corpses or carrion
  3. (n) The art of tabbing out statically- type-checked technical death metal

necrophagy

GitHub CI Hackage BSD-3-Clause license

A type-level, statically-verified Haskell embedded domain specific language (EDSL) for writing guitar tablature.

Named in honor of Necrophagist, the pioneers of modern technical death metal. The music is already technical, what's a little bit of hardcore type-level programming to phase us?

Currently, this library provides:

Future goals include GP5 import/export to make these tabs mesh better with the existing tablature ecosystem.

Transcription workflow is heavily designed around GHCi / cabal repl.

Try it out

>> cabal update
>> cabal install --lib necrophagy

Check out the included example tabs to see if they typecheck; maybe even play around with the kinds and types of the various tracks:

>> cabal repl necrophagy-examples

If you like what you see, you may want to try writing your own tabs based off of one of the example source files. It is as simple as:

>> touch MyTab.hs

{-# LANGUAGE 
  NoMonoLocalBinds, RebindableSyntax, DataKinds,
  OverloadedStrings, TypeOperators, TypeApplications,
  PartialTypeSignatures, NoStarIsType
#-}

module Tab where

import Necrophagy

myTab :: Tablature
myTab = Tablature tabMeta tracks
  where
    tabMeta = TabMeta
      { tabAuthor = ""
      , tabArtist = ""
      , tabName   = ""
      , tabDifficulty = ""
      , tabComments   = mempty
      }

    -- Change this to @Strict if you want equivalence between
    -- the composition durations of all tabs enforced. 
    -- Useful when dealing with polyrhythms.
    tracks = TrackList @Flexible
      [ Track 
          { trackName    = "Player - Instrument"
          , trackProgram = DistortionGuitar `Tuned` EStandard @6
          , trackBody    = myTrack
          }
      ]

myTrack :: _
myTrack = do
  Tempo @240
  Sig @(4/4)
  -- ...And tab away!

>> ghci MyTab.hs
Tab> :t myTrack
Tab> myTab 

For audio playback via midi, the following functions are provided:

Tab> play track -- Plays the specified track from the beginning; Ctrl+C to halt
Tab> at "Marker name" track -- Plays the track starting at specified marker; errors if marker does not exist
Tab> fret @(fretNumber `On` stringNumber) @(tuning) 
Tab> -- ^ Plays the specified note on the specified string; useful while tabbing a song out
Tab> -- Example: fret @(17 `On` 6) @(DStandard 6)
Tab> -- Note: You may need to :set -XTypeApplications -XTypeOperators -xDataKinds for this

You can also conveniently export via the following:

Tab> exportMidi "file.mid" track

Documentation

Every track body is a Composition m m' s s' t t' u c. Let us break the type parameters down:

A Composition has four commands:

Each measure is a Measure o g l. The type parameters are:

A Measure has three commands:

Measures commands are composed via the splicing (#) operator.

Notes

A parsed note is represented as m (f `On` s), with f denoting the fret number and s the string number. m represents the modifier stack, which is the stack of dynamics that are applied to the particular note. For example, Vr (AH (5 `On` 3)) represents a pinch (artificial) harmonic with vibrato on fret 5 of string 3. In this case, the modifier stack m refers to Vr (AH _).

Notes are composed via the combinators (-), (+), and (*). There are four basic notes:

  1. n :: Nat, any type-level natural representing a single fret.
  2. H, a hold/sustain on the previous declared note on the same string.
  3. M, a mute/silent/empty note; the lack of a note, in other words.
  4. X, a dead note.

A sequence of notes is composed via (-), and additionally when inside an arbitrary pair of parentheses, marks a note group g. Note groups can be conveniently replicated via the Rep n g type family. Additionally, a variety of dynamics (effects) can be applied to each note group g. Dynamics can be stacked, internally referred to as a "modifier stack".

Chords are composed via (+) or (*). (*) is what you will normally use, and it reduces down in terms of (+) internally. (+) can only represent modifier stacks that contain an f `On` s type at its root. In other words, (+) requires explicitly-annotated strings on both sides. This is useful for representing small, discontinuous chords. (*), on the other hand, implicitly ascends one string at a time, which is useful for representing continuous chords.

Synonyms

Synonyms expand to note groups, potentially with chords in them. These are useful for concisely describing common measure structures. Two stock synonyms are provided:

Dynamics

Bend Curves

Bend curves are denoted by a type-level list of bend curve vertices (-@-). Each bend curve vertex has the form s -@- t, where s is a fraction representing how many steps (tones) the string is bent at some particular point in time t, which is in turn also a fraction, but with a maximum value of (1/1), relative to the total duration of the note. As an example, the bend curve BenRelC f is defined as follows:

type BenRelC f =
  '[ (0/4) -@- (0 / 12)
   , f     -@- (3 / 12)
   , f     -@- (6 / 12)
   , (0/4) -@- (9 / 12)
   ]  

Four stock bend curves are provided for common use cases:

The parameter f denotes a fraction standing in for the maximum s value of the vertices in the curve.

Programs & Tunings

A 'program' in the context of Necrophagy refers to a tuned instrument, as per MIDI terminology. Programs are constructed via the Tuned :: Instrument -> p -> Program p constructor, where Instrument is any valid MIDI instrument (re-exported from the midi package).

p refers to a specialized tuning name. All tuning names have the kind Nat -> Type; in other words, they are parameterized over a string count. Each specialized tuning name against a string count may have a Tuning instance, which is a poly-kinded list of notes, each specialized to a particular octave number. Notes are defined by the following lifted data declaration:

data Note (n :: Nat)
  = Ab | A | Bb | B | C | Db | D | Eb | E | F | Gb | G  

As an example, the following is the definition of the provided EStandard tuning name and EStandard 6 tuning instance:

data EStandard (n :: Nat) = EStandard

type instance Tuning (EStandard 6)
  = 'E @2
  > 'A @3
  > 'D @3
  > 'G @3
  > 'B @4
  > 'E @4

necrophagy exports and re-exports all the types you need to create your own tunings, or extend existing tuning names to other string counts, in a similar fashion.

Credits

The core of this library was largely written over the course of a single day with some minor follow-up additions in terms of dynamics modifiers, better type errors, et cetera. In closing I would like to pay homage to Necrophagist, '92 - '09, for supplying me with some nostalgic tunes to work against while getting this giant type tetris puzzle just right. I suppose nothing would be more appropriate to conclude this readme with than a recent fan re-recording of an unreleased Necrophagist song.