Copperbox revision 1293.
I've started a new project for UTT - uniform triadic transformations - as they don't look like a good fit for bala-core.
Actually, I'm suspecting that bala-core won't live up to its plan as being a general set of data types and operations for pitch, intervals, meter patterns etc. Formalisms like UTT demand their own representations so having some common 'core' data types hopefully shared between formalisms isn't satisfactory.
Thursday, April 29, 2010
precis-0.3.1
Copperbox revision 1292.
I've made a new release of precis - 0.3.1. I actually made a release at 0.3.0 by svn had a commit problem and while reported a failure while the commit seemingly worked, so I've bumped the version number and remade the binary.
Version 0.3.X added type signature and data declaration diffs.
Copperbox revision 1291 - commit failed on this one, so I consider precis-0.3.0 invalid
I've made a new release of precis - 0.3.1. I actually made a release at 0.3.0 by svn had a commit problem and while reported a failure while the commit seemingly worked, so I've bumped the version number and remade the binary.
Version 0.3.X added type signature and data declaration diffs.
Copperbox revision 1291 - commit failed on this one, so I consider precis-0.3.0 invalid
Wednesday, April 28, 2010
Precis
Copperbox revision 1285.
More work towards being able to compare modules. I've removed the code that transforms a Module into a ModulePrecis. Instead I'll perform (probably repeated) property extracting traversals over a Module to collect properties export lists, type class instances...
More work towards being able to compare modules. I've removed the code that transforms a Module into a ModulePrecis. Instead I'll perform (probably repeated) property extracting traversals over a Module to collect properties export lists, type class instances...
Precis
Copperbox revision 1282.
I've renamed the Metrics module to Properties (and the ModuleMetrics module to ModuleProperties). Code in both modules has been changed to refer to properties rather than metrics. As I wasn't collecting some measure calling them metrics seemed incorrect.
I've renamed the Metrics module to Properties (and the ModuleMetrics module to ModuleProperties). Code in both modules has been changed to refer to properties rather than metrics. As I wasn't collecting some measure calling them metrics seemed incorrect.
Tuesday, April 27, 2010
Precis
Copperbox revision 1281.
More work on metrics. I can now credit 'edit-distance' style differences of lists of properties (currently I still consider these property lists 'metrics' but that might be incorrect). This allows me to list e.g. which modules have been added and removed from a package.
More work on metrics. I can now credit 'edit-distance' style differences of lists of properties (currently I still consider these property lists 'metrics' but that might be incorrect). This allows me to list e.g. which modules have been added and removed from a package.
Precis
Copperbox revision 1279.
I've added more error handling and started a module for collecting metrics. I think I can get better 'differences' between files by collecting metrics over an intact (via haskell-src-exts) parse tree rather than the current method of reducing the parse tree to a simplified baked in representation.
I've added more error handling and started a module for collecting metrics. I think I can get better 'differences' between files by collecting metrics over an intact (via haskell-src-exts) parse tree rather than the current method of reducing the parse tree to a simplified baked in representation.
Precis
Copperbox revision 1278.
I've added initial code for handling file missing and parse errors for the Cabal file. Other error handling (e.g. source file parsing) will need implementing likewise, plus I'll have to move into some Precis-monad to organise it all.
I've added initial code for handling file missing and parse errors for the Cabal file. Other error handling (e.g. source file parsing) will need implementing likewise, plus I'll have to move into some Precis-monad to organise it all.
Monday, April 26, 2010
Precis
Copperbox revision 1277.
I've changed the source code file processing to work on pairs of new and old files rather than build a big lookup table of all modules. Though the code to do this is currently a bit crummy, as I haven't thought about an error handling strategy.
I've changed the source code file processing to work on pairs of new and old files rather than build a big lookup table of all modules. Though the code to do this is currently a bit crummy, as I haven't thought about an error handling strategy.
Precis
Copperbox revision 1276.
Work towards processing pairs of old and new source files at a time.
Ideally I would have done it this way in the first place, but to get something working quickly yesterday I read all files in package and put them in a lookup table. Once in the lookup table I could compare by name between two projects.
Work towards processing pairs of old and new source files at a time.
Ideally I would have done it this way in the first place, but to get something working quickly yesterday I read all files in package and put them in a lookup table. Once in the lookup table I could compare by name between two projects.
Sunday, April 25, 2010
Precis
Copperbox revision 1273.
The main program now works, unfortunately the results aren't very impressive. The parse fails on CPP for instance, instance declarations aren't recognized and when results are recognized they aren't presented very clearly.
Still its a start...
The main program now works, unfortunately the results aren't very impressive. The parse fails on CPP for instance, instance declarations aren't recognized and when results are recognized they aren't presented very clearly.
Still its a start...
Saturday, April 24, 2010
Friday, April 23, 2010
bala-core
Copperbox revision 1267.
I've added yesterday's prototype meter pattern DSL to bala-core.
One thing I didn't think of is how to subdivide the beat into smaller units than 1. Currently I have the one combinator - if a beat has a length of two, then one divides it into 2 unit length notes, but to get say eighth notes in in 2/4 time I need to subdivide again. At the moment, I can't do this.
I've added yesterday's prototype meter pattern DSL to bala-core.
One thing I didn't think of is how to subdivide the beat into smaller units than 1. Currently I have the one combinator - if a beat has a length of two, then one divides it into 2 unit length notes, but to get say eighth notes in in 2/4 time I need to subdivide again. At the moment, I can't do this.
Thursday, April 22, 2010
A DSEL for manipulating meter patterns
I've made a DSEL for manipulating meter patterns. The genesis for the work on Charcoal was to find a DSEL for manipulating musical structures (either pitches or rhythms), but I found that the Charcoal style - using characteristic functions - didn't match well with music as music doesn't seem to have a natural coordinate space.
So I ended up with a DSEL that rewrites the input meter pattern with by augmentation (combining 2 or more beats) or diminution (splitting beats up).
Here is the current draft:
So I ended up with a DSEL that rewrites the input meter pattern with by augmentation (combining 2 or more beats) or diminution (splitting beats up).
Here is the current draft:
module DemoMetrical6 where
type H a = [a] -> [a]
type MeterPattern = [Int]
fromH :: H a -> [a]
fromH = ($ [])
consH :: a -> H a
consH a = (a:)
replicateH :: Int -> a -> H a
replicateH n a = step n id where
step i f | i <= 0 = f
| otherwise = step (i-1) (f . (a:))
--------------------------------------------------------------------------------
hijaz_mp :: MeterPattern
hijaz_mp = [2,2,3]
-- This should be opaque at the module level...
newtype Alg a = Alg {
getAlg :: (Int -> a) -> MeterPattern -> (H a, MeterPattern) }
dim :: Alg a
dim = Alg $ \ f u -> step f u
where
step _ [] = (id,[])
step f (n:ns) = (replicateH n (f 1), ns)
one :: Alg a
one = Alg $ \ f u -> step f u
where
step _ [] = (id,[])
step f (n:ns) = (consH $ f n, ns)
(+++) :: Alg a -> Alg a -> Alg a
(+++) af ag = Alg $ \ f ns -> let (h1,ns') = (getAlg af) f ns
(h2,ns'') = (getAlg ag) f ns'
in (h1 . h2, ns'')
-- Clever, is the (necessary) type restriction on the first
-- parameter too restrictive though?
--
crushWith :: Alg Int -> ([Int] -> Int) -> Alg a
crushWith alg sf = Alg $ \ f u -> let (h,ns') = (getAlg alg) id u
in (consH $ f $ summarize sf h, ns')
summarize :: ([a] -> a) -> H a -> a
summarize f hf = f $ hf []
aug :: Int -> Alg a
aug i | i < 1 = error "aug - must always consume some input"
aug i = (step i one) `crushWith` sum
where
step 1 alg = alg
step n alg = step (n-1) (alg +++ one)
div2 :: (Int -> (Int,Int)) -> Alg a
div2 df = Alg $ \ f u -> step f u
where
step _ [] = (id,[])
step f (n:ns) = let (a,b) = df n in (consH (f a) . consH (f b), ns)
runAlg :: (Int -> a) -> MeterPattern -> Alg a -> [a]
runAlg tc ns alg = fromH $ fst $ (getAlg alg) tc (cycle ns)
-----
one_d_d :: Alg Int
one_d_d = one +++ dim +++ dim
demo1 = runAlg id hijaz_mp one_d_d
demo2 = runAlg id hijaz_mp (aug 3)
demo3 :: [Double]
demo3 = runAlg fromIntegral hijaz_mp (aug 3)
demo4 = runAlg id hijaz_mp (one +++ one +++ div2 (\_ -> (1,2)))
Wednesday, April 21, 2010
Tuesday, April 20, 2010
Charcoal
Copperbox revision 1264.
I've started a new (small) project for drawing pictures in the 'characteristic functional' style like Pan or Clastic. Pictures will only be low-res ASCII - my interest is in the mechanics, hopefully illustrating how pictures from Point -> Greyscale work. Clastic is a bit too large, Pan is not open source.
Currently I can draw solid filled pictures only.
I've started a new (small) project for drawing pictures in the 'characteristic functional' style like Pan or Clastic. Pictures will only be low-res ASCII - my interest is in the mechanics, hopefully illustrating how pictures from Point -> Greyscale work. Clastic is a bit too large, Pan is not open source.
Currently I can draw solid filled pictures only.
Monday, April 19, 2010
bala-core
Copperbox revision 1262.
Work on a different representation of Pitch and Intervals. Pitch is represented by pitch-letter and semitone count (octave and accidental can be derived from this). With this representation 'vector-space' operations seem quite a bit easier to define - subtracting two pitches to get an interval; adding an interval to a pitch to get a pitch.
Work on a different representation of Pitch and Intervals. Pitch is represented by pitch-letter and semitone count (octave and accidental can be derived from this). With this representation 'vector-space' operations seem quite a bit easier to define - subtracting two pitches to get an interval; adding an interval to a pitch to get a pitch.
wumpus-core
Copperbox revision 1261.
Updates to the dependencies - removing dependency on Data.Aviary.
Updates to the dependencies - removing dependency on Data.Aviary.
Sunday, April 18, 2010
Neume
Copperbox revision 1258.
I've removed the Extra.Extended module that was inherited from Mullein with a module solely for Tab notes - i.e. notes with string number annotations.
Extra.Extended was quite grisly as it served rather different purposes in Mullein. I expect that for Neume each extended note type - i.e. notes with string annos, fret diagrams - will have its own module and 'annotation' types rather than trying to share common types (which was the model Extra.Extended was following).
Extended glyphs will share the common primitive glyph types of course, Glyph (for notes, chords, graces...) or MarkupGlyph (for Fret diagrams etc).
I've removed the Extra.Extended module that was inherited from Mullein with a module solely for Tab notes - i.e. notes with string number annotations.
Extra.Extended was quite grisly as it served rather different purposes in Mullein. I expect that for Neume each extended note type - i.e. notes with string annos, fret diagrams - will have its own module and 'annotation' types rather than trying to share common types (which was the model Extra.Extended was following).
Extended glyphs will share the common primitive glyph types of course, Glyph (for notes, chords, graces...) or MarkupGlyph (for Fret diagrams etc).
Neume
Copperbox revision 1257.
I've moved the modules AbcFormat and LilyPondFormat from Extra to Core. This means that simple scores (i.e. ones with only notes, not percussion or guitar chords) can work by importing modules from Neume.Core to ABC or LilyPond only, though they will miss e.g. all the named notes.
This was the intention when I moved some code out into Extra in the first place - however as I was developing, some code didn't naturally fit this distinction. Now that I've much of the work prototyped at least, its easier to see where things should go.
I've moved the modules AbcFormat and LilyPondFormat from Extra to Core. This means that simple scores (i.e. ones with only notes, not percussion or guitar chords) can work by importing modules from Neume.Core to ABC or LilyPond only, though they will miss e.g. all the named notes.
This was the intention when I moved some code out into Extra in the first place - however as I was developing, some code didn't naturally fit this distinction. Now that I've much of the work prototyped at least, its easier to see where things should go.
Saturday, April 17, 2010
Neume
Copperbox revision 1255.
Guitar tab output is now working in the GuitarTab.hs example.
The current Neume has as much functionality (overlays, repeats, guitar tab, fret diagrams) as any of my previous attempts so I've made an archive Neume-0.2.0 as a checkpoint. Its still a long way off being release quality - a lot of the code has been written quickly to get some kind of output; but it is something of a high water mark.
New picture on Flickr of tab output.
http://www.flickr.com/photos/44929957@N03/4527449707/
Guitar tab output is now working in the GuitarTab.hs example.
The current Neume has as much functionality (overlays, repeats, guitar tab, fret diagrams) as any of my previous attempts so I've made an archive Neume-0.2.0 as a checkpoint. Its still a long way off being release quality - a lot of the code has been written quickly to get some kind of output; but it is something of a high water mark.
New picture on Flickr of tab output.
http://www.flickr.com/photos/44929957@N03/4527449707/
Friday, April 16, 2010
Thursday, April 15, 2010
Neume
Copperbox revision 1251.
I've changed the shorthand constructors in NamedElements so that the will be able to handle annotations like string number better. I've also removed a lot ones that weren't used and added an underscore suffix to the note names. This makes the note names rather cumbersome, but it means they aren't name-space squatting for good, single letter names.
I've changed the shorthand constructors in NamedElements so that the will be able to handle annotations like string number better. I've also removed a lot ones that weren't used and added an underscore suffix to the note names. This makes the note names rather cumbersome, but it means they aren't name-space squatting for good, single letter names.
Neume
Copperbox revision 1250.
I've changed the Note type so that it no longer carries duration - instead the Note constructor of the Glyph type carries duration. This is more consistent with the other Glyph constructors - I don't know why I hadn't spotted the inconsistency earlier.
I've changed the Note type so that it no longer carries duration - instead the Note constructor of the Glyph type carries duration. This is more consistent with the other Glyph constructors - I don't know why I hadn't spotted the inconsistency earlier.
Neume
Copperbox revision 1249.
I've changed the type of the note constants (actually more constructors than constants). This is work towards adding string number annotations for tabs. Neume inherited quite a lot of code from Mullein for these features - unfortunately the code is all over the place as it never really got used.
I've changed the type of the note constants (actually more constructors than constants). This is work towards adding string number annotations for tabs. Neume inherited quite a lot of code from Mullein for these features - unfortunately the code is all over the place as it never really got used.
Wednesday, April 14, 2010
Neume
Copperbox revision 1248.
I've made the Guitar Chords example a bit more satisfying. A new picture of the output is on Flickr...
http://www.flickr.com/photos/44929957@N03/4520948647/
I've made the Guitar Chords example a bit more satisfying. A new picture of the output is on Flickr...
http://www.flickr.com/photos/44929957@N03/4520948647/
Tuesday, April 13, 2010
Neume
Copperbox revision 1245.
I've implemented a new traversal for changing Duration to (Maybe Duration) for LilyPond. In the end I decided not to use a traversal based on the last post (i.e. separating shape and contents), and I'm using one that tracks an index instead so it knows when it is at the first note in a bar.
The new traversal is polymorphic on glyph - whereas the previous one only handled 'standard' glyphs.
I've implemented a new traversal for changing Duration to (Maybe Duration) for LilyPond. In the end I decided not to use a traversal based on the last post (i.e. separating shape and contents), and I'm using one that tracks an index instead so it knows when it is at the first note in a bar.
The new traversal is polymorphic on glyph - whereas the previous one only handled 'standard' glyphs.
Shape contents traversal...
Here's a bit of code using Neume's StateMap class an a Hughes list that separates the shape of data from its contents. In the code here elementary could also be coded as map (map f), but more inventive "elemenentary" functions are possible.
module ShapeContents where
import Neume.Core.Utils
import Neume.Core.Utils.HList
elementary :: (a -> b) -> [[a]] -> [[b]]
elementary f xss = reassemble (map f contents) shape
where
(shape, contents) = decompose xss
decompose :: [[a]] -> ([[()]],[a])
decompose xss = fmap2b ($ []) $ stmap fn id xss
where
fn stf row = (row1, stf . h1) where (row1,h1) = decompose1 row
decompose1 :: StateMap f => f a -> (f (), H a)
decompose1 = stmap fn id where
fn stf a = ((), stf `snoc` a)
reassemble :: [a] -> [[()]] -> [[a]]
reassemble xs shape = fst $ stmap (stmap fn) xs shape where
fn (s:st) () = (s,st)
fn _ () = error $ "reassemble - run out of data"
Neume
Copperbox revision 1244.
I've tidied up a lot of the stmap instances by using a combinator stBinary that merges two stateful maps.
I've tidied up a lot of the stmap instances by using a combinator stBinary that merges two stateful maps.
Monday, April 12, 2010
Neume
Copperbox revision 1240.
The example ABC_B6.hs is now working again - as the new beam grouping code has been fixed. Other examples won't be working at the moment, as all the LilyPond code needs changing to use the Phrase datatype rather than the StaffPhrase type and incorporate the new bar splitting code.
The example ABC_B6.hs is now working again - as the new beam grouping code has been fixed. Other examples won't be working at the moment, as all the LilyPond code needs changing to use the Phrase datatype rather than the StaffPhrase type and incorporate the new bar splitting code.
Neume
Copperbox revision 1239.
Work towards unifying the phrase syntax. I've changed ABC to use the new beam grouping / bar splitting and to use the Phrase type rather than the StaffPhrase type. Currently there's a problem that NoteLists are converted to lists of CExprs at the wrong time. This is stopping beam grouping working properly.
Work towards unifying the phrase syntax. I've changed ABC to use the new beam grouping / bar splitting and to use the Phrase type rather than the StaffPhrase type. Currently there's a problem that NoteLists are converted to lists of CExprs at the wrong time. This is stopping beam grouping working properly.
Sunday, April 11, 2010
Neume
Copperbox revision 1237.
I've changed the NumMeasured type class to a simpler one DMeasured that doesn't use a type family.
This is part of a round of work to simplify and unify the syntax which is currently split between five modules. The first part of this work will actually be simplifying beam grouping yet again... oh well.
I've changed the NumMeasured type class to a simpler one DMeasured that doesn't use a type family.
This is part of a round of work to simplify and unify the syntax which is currently split between five modules. The first part of this work will actually be simplifying beam grouping yet again... oh well.
Saturday, April 10, 2010
Friday, April 9, 2010
Type level success?
I've never had much success with type level programming, but maybe this new score representation for Neume means I'm improving (as the name indicates this particular one took seven attempts).
The shape of the score (linear sections, repeated sections, alternative endings), is encoded in the type. That the Show and Functor instance were easy to code indicates that the it might actually be useful. Previously when I've tried type level programming I've ended up with structures that I couldn't actually work with.
The shape of the score (linear sections, repeated sections, alternative endings), is encoded in the type. That the Show and Functor instance were easy to code indicates that the it might actually be useful. Previously when I've tried type level programming I've ended up with structures that I couldn't actually work with.
{-# LANGUAGE GADTs #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE TypeOperators #-}
module GADTSection7 where
data Z = Z
data x :. xs = x :. xs
data TLinear
data TRepeat
data TAltRep
data TList shape e where
Nil :: TList Z e
Linear :: e -> TList shape e -> TList (TLinear :. shape) e
Repeat :: e -> TList shape e -> TList (TRepeat :. shape) e
AltRep :: e -> [e] -> TList shape e -> TList (TAltRep :. shape) e
-- Good - shape of the list reflected in its type...
tune0 = Linear "...o..o" $ Nil
tune1 = Linear "....o..o" $ Linear "...o..o" $ Nil
tune2 = Repeat "o.o..o.o" $ Nil
-- Good - disallows junk...
-- tune3 = Linear "....o..o" $ Linear 3000 $ Nil
sameType :: TList sh e -> TList sh e -> Bool
sameType _ _ = True
-- Good - throws error...
-- > sametype tune1 tune2
tune4 = Repeat "........" $ Nil
demo01 = sameType tune2 tune4
tune5 = Linear "o.o....." $ Nil
-- Good ...
-- sameType enforces sameShape not just sameLength
-- demo02 = sameType tune4 tune5
sameShape :: TList sh e -> TList sh e' -> Bool
sameShape _ _ = True
tune6 = Linear 3000 $ Nil
demo03 = sameShape tune5 tune6
instance Functor (TList shape) where
fmap _ Nil = Nil
fmap f (Linear e xs) = Linear (f e) (fmap f xs)
fmap f (Repeat e xs) = Repeat (f e) (fmap f xs)
fmap f (AltRep e es xs) = AltRep (f e) (map f es) (fmap f xs)
instance Show e => Show (TList shape e) where
showsPrec _ Nil = showString "Nil"
showsPrec _ (Linear e xs) =
showString "Linear" . spS . shows e . spS . appS . spS . shows xs
showsPrec _ (Repeat e xs) =
showString "Repeat" . spS . shows e . spS . appS . spS . shows xs
showsPrec _ (AltRep e es xs) =
showString "AltRep" . spS . shows e . spS . showList es . spS
. appS . spS . shows xs
tune7 = AltRep "o.o.o..o" ["o.", ".o"] $ Nil
spS :: ShowS
spS = showChar ' '
appS :: ShowS
appS = showChar '$'
Wednesday, April 7, 2010
Neume
Copperbox revision 1231.
I've made an archive of the current code. Whilst Neume isn't outwardly useful and a lot of the code is far from pretty, all the examples are currently working so it merits check pointing.
I've made an archive of the current code. Whilst Neume isn't outwardly useful and a lot of the code is far from pretty, all the examples are currently working so it merits check pointing.
Neume
Copperbox revision 1230.
I've fixed the bug where LilyPond was getting relative pitch transformations wrong with overlays. This means that the Overlay1 example is now printing correctly for both ABC and LilyPond...
Unfortunately just to get output the code has become horrible and ad hoc - I think this version of the repository it going to be a high water mark (or cynically a low water mark) for Neume, as I'm going to have to devise a better way of creating and processing scores - i.e. note lists that might be overlayed, repeated etc.
I've fixed the bug where LilyPond was getting relative pitch transformations wrong with overlays. This means that the Overlay1 example is now printing correctly for both ABC and LilyPond...
Unfortunately just to get output the code has become horrible and ad hoc - I think this version of the repository it going to be a high water mark (or cynically a low water mark) for Neume, as I'm going to have to devise a better way of creating and processing scores - i.e. note lists that might be overlayed, repeated etc.
Tuesday, April 6, 2010
Neume
Copperbox revision 1227.
More work towards overlays in LilyPond - though still nothing to show for it but messy, broken code. More usefully I've corrected a bug in the ABC output where the last alternative repeat ending was incorrectly finalized with a repeat sign. It is now finalized with a double bar.
More work towards overlays in LilyPond - though still nothing to show for it but messy, broken code. More usefully I've corrected a bug in the ABC output where the last alternative repeat ending was incorrectly finalized with a repeat sign. It is now finalized with a double bar.
Monday, April 5, 2010
Neume
Copperbox revision 1223.
I've corrected a long standing but previously unnoticed bug in the LilyPond duration to optional duration transformation.
I've also implemented some of the Show instances to print shorthand, rather than use the derived instances that print all the constructors.
I've corrected a long standing but previously unnoticed bug in the LilyPond duration to optional duration transformation.
I've also implemented some of the Show instances to print shorthand, rather than use the derived instances that print all the constructors.
Sunday, April 4, 2010
Neume
Copperbox revision 1222.
More work towards overlays in LilyPond - a prototype is in place that generates LilyPond code, however it generates bad code. The code has a trivial problem that it doesn't yet use the parallelMusic command which I discovered recently. It also has a serious problem that parallelMusic doesn't work well with repeat symbols - I didn't know this until I started hand editing the generated code to make it print.
More work towards overlays in LilyPond - a prototype is in place that generates LilyPond code, however it generates bad code. The code has a trivial problem that it doesn't yet use the parallelMusic command which I discovered recently. It also has a serious problem that parallelMusic doesn't work well with repeat symbols - I didn't know this until I started hand editing the generated code to make it print.
Neume
Copperbox revision 1221.
Work towards overlays (parallel music) for LilyPond.
LilyPond is significantly harder candidate for overlays than ABC. Rendering can be stateful - so I sometimes must use stmap rather than fmap. Also overlays can have different types i.e. one overlay line can be guitar chords and one normal notes. I'm committing the current work even though it is a way of working, as its in danger of getting complicated, ad hoc very quickly.
Work towards overlays (parallel music) for LilyPond.
LilyPond is significantly harder candidate for overlays than ABC. Rendering can be stateful - so I sometimes must use stmap rather than fmap. Also overlays can have different types i.e. one overlay line can be guitar chords and one normal notes. I'm committing the current work even though it is a way of working, as its in danger of getting complicated, ad hoc very quickly.
Saturday, April 3, 2010
Neume
Copperbox revision 1220.
Finally, a successful implementation that provides both overlays and score syntax (i.e straight sections, repeats and repeats with alternative endings). Currently ABC only and only overlays of size two.
I'm going to use an arity family of functions vis-a-vis zip2, zip3 etc. Trying something like a typed printf is too complicated given that I have to send quite a few parameters to the rendering function and the 'variable arity' represents the size of paired tuples within a functorial datatype.
Finally, a successful implementation that provides both overlays and score syntax (i.e straight sections, repeats and repeats with alternative endings). Currently ABC only and only overlays of size two.
I'm going to use an arity family of functions vis-a-vis zip2, zip3 etc. Trying something like a typed printf is too complicated given that I have to send quite a few parameters to the rendering function and the 'variable arity' represents the size of paired tuples within a functorial datatype.
Thursday, April 1, 2010
Subscribe to:
Posts (Atom)
Blog Archive
-
▼
2010
(890)
-
▼
April
(82)
- utt
- precis-0.3.1
- Precis
- precis-0.2.0
- Precis
- Precis
- Precis
- Precis
- Precis
- Precis
- Precis
- Precis
- Precis
- Precis
- Precis
- Precis
- Precis
- Precis
- Precis
- Precis
- Precis
- Precis
- Precis
- Precis
- bala-core
- bala-core
- A DSEL for manipulating meter patterns
- Charcoal
- Charcoal
- Charcoal
- bala-core
- bala-core
- wumpus-core
- bala-core
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Shape contents traversal...
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Type level success?
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
- precis-0.1.0
- Neume
- Neume
- Neume
- Neume
- Neume
- Neume
-
▼
April
(82)
About Me
- Stephen Tetley
- 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.