% first line Data.PcSets.Compact % This file is part of gpcsets: Pitch Class Sets for Haskell % Copyright 2009 by Bruce H. McCosar. % Distributed under a BSD3 license; see the file 'LICENSE' for details. \chapter{Data.PcSets.Compact} \section{Introduction} \begin{quote} {\bf Important Note.} My philosophy in designing these modules has been to avoid pointless errors and exceptions, that is, to create acceptable, sane default operations. I assume if someone is going to try to run the text of Tolstoy's "War and Peace" through the String-to-Pitch-Class-Set routines in this module, they are prepared to accept the default behavior, which is to silently ignore much of the input. This makes much more sense than attempting to handle every possible input string (and provide a suitable error message for each case). \end{quote} \subsection{The Module Export List} \begin{code}
{-|
  This module translates Pitch Class Sets to and from /Compact Format/.
  In Compact Format, data such as StdSet [0,4,7,11] could be represented
  by the string 047B, which uses a single alphanumeric character for each
  pitch class element.

  Limitations: this module is only usable for pitch class sets of modulus
  36 or below. Beyond that, it's not really certain that a compact format
  would be of any practical use.
-}
module Data.PcSets.Compact
  (
    -- * Constructors: Compact Format to PcSet
      toGenSet
    , toStdSet
    , toStdSet'
    , toGenRow
    , toStdRow
    , toStdRow'
    -- * Abbreviators: PcSet to Compact Format
    , compact
    , compact'
  )
where
\end{code} \subsection{The Module Import List} \begin{code}
import qualified Data.PcSets as P
\end{code} \section{Constructors: Compact Format to PcSet} \subsection{Pitch Class Sets} \subsubsection{toGenSet} \begin{code}
{-|
  Creates a new General Pitch Class Set of modulus /n/. Alphanumeric
  character values 0-9 and A-Z represent the numbers 0 to 36. Other
  inputs, including whitespace, are ignored.
-}
toGenSet :: Int -> String -> P.GenSet
toGenSet n = P.genset n . trBase36
\end{code} \subsubsection{toStdSet} \begin{code}
{-|
  Creates a new Standard (modulus 12) Pitch Class Set. Here, input
  characters 0-9 count as their decimal equivalents; the letter /A/
  stands for 10, and the letter /B/ stands for 11. Other inputs,
  including whitespace, are ignored.
-}
toStdSet :: String -> P.StdSet
toStdSet = P.stdset . trBase36
\end{code} \subsubsection{toStdSet'} \begin{code}
{-|
  Creates a new Standard (modulus 12) Pitch Class Set, using an alternative
  duodecimal format. Here, input characters 0-9 count as their decimal
  equivalents; the letter /T/ stands for 10, and the letter /E/ stands for
  11. Other inputs, including whitespace, are ignored.
-}
toStdSet' :: String -> P.StdSet
toStdSet' = P.stdset . trBase12
\end{code} \subsection{Tone Rows} \subsubsection{toGenRow} \begin{code}
{-|
  Creates a new General Tone Row of modulus /n/. Alphanumeric character
  values 0-9 and A-Z represent the numbers 0 to 36. Other inputs, including
  whitespace, are ignored. Since Tone Rows must contain all possible
  elements, an incomplete entry list will result in a new row with the
  missing tones added at the end.
-}
toGenRow :: Int -> String -> P.GenRow
toGenRow n = P.genrow n . trBase36
\end{code} \subsubsection{toStdRow} \begin{code}
{-|
  Creates a new Standard (modulus 12) Tone Row. Here, input characters 0-9
  count as their decimal equivalents; the letter /A/ stands for 10, and
  the letter /B/ stands for 11. Other inputs, including whitespace, are
  ignored. (Also, see notes for 'toGenRow'.)
-}
toStdRow :: String -> P.StdRow
toStdRow = P.stdrow . trBase36
\end{code} \subsubsection{toStdRow'} \begin{code}
{-|
  Creates a new Standard (modulus 12) Tone Row, using an alternative
  duodecimal format. Here, input characters 0-9 count as their decimal
  equivalents; the letter /T/ stands for 10, and the letter /E/ stands for
  11. Other inputs, including whitespace, are ignored. (Also, see notes for
  'toGenRow'.)
-}
toStdRow' :: String -> P.StdRow
toStdRow' = P.stdrow . trBase12
\end{code} \section{Abbreviators: PcSet to Compact Format} \subsection{General Case} \begin{code}
{-|
  Translates a Pitch Class Set or Tone Row to Compact Format. Values from
  0-9 are translated as the characters 0-9; values from 10 to 35 are
  translated as charaters A-Z. Values which are out of the representable
  range are ignored, therefore this function is not suitable for sets of
  modulus 37 or greater.
-}
compact :: P.PcSet a => a -> String
compact = filter (/= '#') . map f . P.elements
  where f n
          | 0 <= n && n <= 9 = toEnum (n + 48)
          | 9 < n && n < 37  = toEnum (n + 55)
          | otherwise        = '#' -- ignore out of range
\end{code} \subsection{Specialized Standard} \begin{code}
{-|
  This function is identical to 'compact', except that Standard (modulus
  12) sets and rows are rendered using 'T' for 10 and 'E' for 11.
-}
compact' :: P.PcSet a => a -> String
compact' ps = if P.modulus ps /= 12 then compact ps
    else filter (/= '#') . map f . P.elements $ ps
  where f n
          | 0 <= n && n <= 9 = toEnum (n + 48)
          | n == 10          = 'T'
          | n == 11          = 'E'
          | otherwise        = '#' -- ignore out of range
\end{code} \section{Not Exported} \subsection{Alphanumeric Translators} \subsubsection{Base 36} \begin{code}
trBase36 :: String -> [Int]
trBase36 = filter (>= 0) . map f
  where f c
          | '0' <= c && c <= '9' = fromEnum c - 48
          | 'A' <= c && c <= 'Z' = fromEnum c - 55
          | otherwise            = -1 -- ignore nonsense
\end{code} \subsubsection{Duodecimal} \begin{code}
trBase12 :: String -> [Int]
trBase12 = filter (>= 0) . map f
  where f c
          | '0' <= c && c <= '9' = fromEnum c - 48
          | c == 'T'             = 10
          | c == 'E'             = 11
          | otherwise            = -1 -- ignore nonsense
\end{code} % last line Data.PcSets.Compact