Sunday, February 28, 2010

Neume

Copperbox revision 1154.

Work on a new beam grouping and bar splitting algorithm.

This one seems a lot more promising than previous attempts. What I'm doing is segmenting into metrical units that match each division of a meter pattern - say if I'm in 4-4 time with two beam groups each of a half note. I split the input stream into chunks of a half note in duration (possibly with some borrow). To turn the segmented stream into bars I take two chunks at a time and amalgamate them into a bar (beam grouping inside the chunk when necessary).

This is much simpler than what I was trying before, where I had split the input into single notes and beam groups and had to count them all again to form a bar.

I've easily accounted for a start anacrusis with the new algorithm and in my head it works for n-ary tuplets, though I have to work the details out - I'm still not sure what form n-ary tuplets should have in the intermediate syntax tree.

Neume

Copperbox revision 1153.

Work on summing the duration of PletTrees. It seems wrong at the moment but that might be my test instead, so I want the code check pointed.

Saturday, February 27, 2010

Neume

Copperbox revision 1152.

Back to work on Neume...

This time I'm working with input data type that can handle n-ary tuplets from the beginning. Last time bracketing quickly became too complicated, before I even thought about triplets and duplets, so I've decided to put them in from the start. Unfortunately this means I'll have to work with trees rather than simple linear lists - tuplets can be nested so this mandates trees.

Thursday, February 25, 2010

kangaroo

Copperbox revision 1151.

I've added the row formatting module from Hurdle to JoinPrint (where it belongs) and a couple of missing formatters (list, tupled, and semiBraces).

Wednesday, February 24, 2010

Hurdle-0.4.0

Copperbox revision 1150.

I've made a new release of Hurdle - no new functionality, but it does use the latest Kangaroo.

Hurdle

Copperbox revision 1149.

I've worked out a new formatter for tables via the TypeCase pattern. When integrated it should improve the TextDump module quite a bit, currently its quite horrible.

Tuesday, February 23, 2010

kangaroo-0.4.0

Copperbox revisions 1147 & 1148.

A new release of kangaroo with the JoinPrint improvements.

Revision 1147 has the new tar archive with the latest cabal file in the archive. Unfortunately I missed committing the latest cabal file with 1147, so it is committed at 1148.

Monday, February 22, 2010

kangaroo

Copperbox revision 1146.

The AR example parser now prints hex dumps as it runs. Kangaroo seems about ready for a new release, though I'll sort that out tomorrow (too late today).

kangaroo

Copperbox revision 1145.

I've improved the hexdump for arrays and added a moveForward primitive to the the ParseMonad.

kangaroo

Copperbox revision 1144.

I've added a hexdump function that works directly on IOUArrays. Currently the definition is pretty clumsy though, and it needs some more thought (it might not even work correctly).

Sunday, February 21, 2010

kangaroo

Copperbox revision 1143.

I've Haddock documented all the exported functions for JoinPrint.Core.

kangaroo

Copperbox revision 1142.

I've added a separate VDoc type to JoinPrint to represent multi-line documents. This is because horizontal documents track their (horizontal) width. Previously, vertically stacking documents just combined both widths - this was a known bug, but I had rather forgotten about it.

I could track say max width, first width or last width, but none of them seem ideal and seems to make better sense to have a separate multi-line doc type (VDoc) instead. This does change the interface a bit though - previously it was more or less compatible with PPrint.

Friday, February 19, 2010

kangaroo

Copperbox revision 1141.

I've added a new example to Kangaroo - a parser for AR archives. Soon I'll remove the MIDI example as it is too large and I want something smaller as I'm going to experiment with some new parsing combinators.

Thursday, February 18, 2010

precis

Copperbox revision 1140.

More work on Precis - I've improved how file paths to the modules are extracted from the Cabal file.

Also I've done some work on monadic combinators for data-aviary, what I've come up with so far isn't very good though.

Wednesday, February 17, 2010

precis

Copperbox revision 1139.

I've started to use haskell-src-exts so I can look at the export lists from modules.

Tuesday, February 16, 2010

precis

Copperbox revision 1138.

Better resolution of paths relative to the Cabal file - the example I'm working with now finds its modules correctly.

precis

Copperbox revision 1137.

I'm taking a break from Neume to look at Precis again. With this commit, I've reworked the module extraction code - it now works better with the Cabal 'Distribution' library datatypes.

Strangest program I ever wrote #10001 (Nested datatypes)

I've been looking at nested datatypes to see if they would have some benefit for simplifying beam grouping, maybe they would but they are pretty complicated in themselves.

Here's a List nested datatype with just fmap and length operations, it took a lot of head scratching to get this far:




{-# LANGUAGE TypeSynonymInstances #-}
{-# OPTIONS -Wall #-}

-- Hinze, Manufacturing Datatypes page 9
-- Okasaki, From Fast Exponentiation ... page 30


module List where

import Data.Char ( chr ) -- for tests
import Prelude hiding ( length )

type Vector = Vector' ()
data Vector' t a = Zero t
| Succ (Vector' (a,t) a)
deriving (Eq,Show)

type List = Vector


list00 :: List Int
list00 = Zero ()

list01 :: List Int
list01 = Succ (Zero (1, ()))

list02 :: List Int
list02 = Succ (Succ (Zero (1, (2, ()))))

list03 :: List Int
list03 = Succ (Succ (Succ (Zero (1, (2, (3, ()))))))



mapL :: (a -> b) -> List a -> List b
mapL = mapV ()


-- Perform the map by destructing the list, applying f to the
-- /head/ and recurvisely working on the tail, then consing the
-- structure back into shape.
--
-- The initial value for /Zero/ needs to be supplied as a
-- parameter.
--

mapV :: t -> (a -> b) -> Vector' t a -> Vector' t b
mapV t0 f xs = let ans = desV xs in
case ans of
Nothing -> Zero t0
Just (a,rest) -> consV (f a) (mapV t0 f rest)


instance Functor List where
fmap = mapV ()


length :: Vector a -> Int
length = lengthV

lengthV :: Vector' t a -> Int
lengthV (Zero _) = 0
lengthV (Succ xs) = 1 + lengthV xs


cons :: a -> List a -> List a
cons a xs = consV a xs

consV :: a -> Vector' t a -> Vector' t a
consV a (Zero b) = Succ (Zero (a, b))
consV a (Succ xs) = Succ (consV a xs)

list04 :: List Int
list04 = cons 0 list03

-- Helps to have a destructor...

des :: List a -> Maybe (a, List a)
des = desV

desV :: Vector' t a -> Maybe (a, Vector' t a)
desV (Zero _) = Nothing
desV (Succ (Zero (a,bs))) = Just (a, Zero bs)
desV (Succ xs) = case desV xs of
Nothing -> Nothing
Just (a,xs') -> Just (a, Succ xs')

list05 :: List Char
list05 = fmap (chr . (+64)) list04

Sunday, February 14, 2010

joinlist-0.3.0

Copperbox revision 1136.

A new release of joinlist adding views as per Data.Sequence.

Thursday, February 11, 2010

Neume

Copperbox revision 1135.

More work on bracketing for beam groups, bracketing for bars is work remaining.

Wednesday, February 10, 2010

Neume

Copperbox revision 1134.

The Bulgarian6 example now compiles, but some of the functions are stubbed so it doesn't run the main one being bracketing. Indeed, now that I've worked up enough code to get to CExpr type (that should handle beam groups and tuplets) I'm having my doubts as to whether it is adequate for the job.

Neume

Copperbox revision 1133.

I've changed the LilyPond rewriting functions to use the StateMap and StateMap2, StateMap3 type classes.

Neume

Copperbox revision 1132.

I've implemented the ABC output functions that were stubbed in the last commit. Also I've added the 'Bulgarian6' example from Mullein, although there are some big pieces missing that are stopping it running.

Neume

Copperbox revision 1131.

I've added the ABC code from Mullein, though quite a lot is stubbed out at the moment. I've also added bifunctor and ternary (?) functor classes to help manipulate notes (parameteric on annotation, pitch and duration).



class FMap2 f where
fmap2 :: (a -> u) -> (b -> v) -> f a b -> f u v

class FMap3 f where
fmap3 :: (a -> u) -> (b -> v) -> (c -> w) -> f a b c -> f u v w


fmap2a :: FMap2 f => (a -> u) -> f a b -> f u b
fmap2a f = fmap2 f id

fmap3a :: FMap3 f => (a -> u) -> f a b c -> f u b c
fmap3a f = fmap3 f id id

fmap3b :: FMap3 f => (b -> v) -> f a b c -> f a v c
fmap3b g = fmap3 id g id

Tuesday, February 9, 2010

Neume

Copperbox revision 1130.

I've added more code back from Mullein - the named elements and the extended data types (e.g. drum notes for LilyPond). The extended module might change quite a bit...

Neume

Copperbox revision 1129.

I've added a Functor like class with a stateful version of fmap. I want to see if it seems more convenient than using mapM and a state monad.


class StateMap f where
stmap :: (a -> st -> (b,st)) -> f a -> st -> (f b,st)

Neume

Copperbox revision 1128.

Mullein M2 is now called Neume. The name is meant to indicate that Neume is a somewhat primitive system for music scores.

I've changed the syntax in this commit - staff syntax (the complicated one with beam groups, tuplets, chords and grace notes) is in a distinct module to markup (the simpler one for chord diagrams etc.) and doc syntax (for post processing after rendering to ABC or LilyPond, e.g. adding bar lines, repeats...).

Monday, February 8, 2010

Mullein M2

Copperbox revision 1127

I've partially revised the syntax so that Bars and CExprs (tuplets | beam groups | atomic glyphs) are parametric only on a single parameter rather than three. Being parametric on annotation, pitch and duration seemed more appropriate when I was experimenting with KURE but now I think it is a burden instead.

Also I think having an AExpr for a single glyph or grace notes is not great. Originally I thought this was an improvement on Mullein which had grace notes as one of the constructors on the glyph type (I didn't like one of the glyph constructors having one-or-more pitches and durations when all the other constructors had zero-or-one pitch and durations). Unfortunately having AExpr's (single glyph | grace notes) is making bracketing difficult - it is much harder to account for BeamExtremity in two places in the syntax tree, rather than only on 'glyphs'.

I'll remove AExprs in the next commit, for the moment I want to checkpoint them.

Hurdle and ZFont

Copperbox revision 1126.

I've updated both Hurdle and ZFont to use the latest release of Kangaroo.

Sunday, February 7, 2010

ZMidi

Copperbox revision 1125.

ZMidi - some improvements to the parser.

kangaroo-0.3.0

Copperbox revision 1124.

I've made a new release of Kangaroo with today's documentation additions and code clean-up on the ParseMonad module and export lists of the top level modules.

Kangaroo

Copperbox revision 1123.

A round of work adding some polish to Kangaroo. I've Haddock doc-ed the Prim module and change its interface slightly.

ZMidi

Copperbox revisions 1121 & 1122.

I've updated ZMidi to use Kangaroo rather than its own binary parser.

Saturday, February 6, 2010

Mullein M2

Copperbox revision 1120.

I've simplified the 'worlds most complex unfold' and it now works - at least for well formed input.

For reference, here's the type signature of the final version. I needed lexically scoped type variables so I could put type signatures on the internal definitions:



beamingAUnfold :: forall outer_state inner_state a interim ans.
([interim] -> Maybe ans)
-> (outer_state -> inner_state -> Maybe (outer_state,inner_state))
-> (a -> inner_state -> BStep interim ans inner_state)
-> outer_state -> inner_state -> [a] -> ([ans],[a])

Mullein M2

Copperbox revision 1119.

For beam group splitting, I've written possibly the worlds most complex unfold - so complicated that I can't work out how to seed it. I'm not proud of the complexity and hopefully I can simplify it as I work out how to seed it, but I'm committing it now to checkpoint it in all its glory.

Friday, February 5, 2010

Mullein M2

Copperbox revision 1118.

More work on bracketing unfolds, though they have now got to complicated to work with - so clearly I'm doing something wrong. I'm committing in the current work as a checkpoint, though again it is pretty scrappy.

Mullein M2

Copperbox revision 1117.

First commit of new code for bar splitting and beam grouping (what I call bracketing). The code is very scrappy at the moment as I'm trying to work out how much I can do with specialized unfolds. The previous hand crafted bracketing code really was quite "rube goldberg", hopefully if I can use unfolds the new code should be more palatable.

Wednesday, February 3, 2010

Mullein M2

Copperbox revision 1116.

I've added the LilyPond relative pitch transformation.

Mullein M2

Copperbox revision 1115.

Added absolute pitch transformation to the LilyPond output code.

Tuesday, February 2, 2010

Mullein M2

Copperbox revision 1114.

Some work on rewriting duration and pretty printing for LilyPond.

Monday, February 1, 2010

Mullein M2

Copperbox revision 1113.

I've reworked the syntax again so that I can handle "above the staff" glyphs like chord diagrams.

Blog Archive

About Me

My photo
Disambiguating biog as there are a few Stephen Tetley's in the world. I'm neither a cage fighter or yachtsman. I studied Fine Art in the nineties (foundation Bradford 1992, degree Cheltenham 1992 - 95) then Computing part-time at Leeds Met graduating in 2003. I'm the Stephen Tetley on Haskell Cafe and Stackoverflow.