[Haskell-cafe] philosophy of Haskell

2010-08-07 Thread Michael Mossey
When I started to study Haskell, I was surprised that so much emphasis was 
placed on simple things. Monads were introduced to me as basically a 
wrapper, and a bind function that unwrapped something and wrapped something 
else back up again. I didn't understand what the fuss was about. Later I 
saw the amazing feats of expressiveness that were possible. I scratched my 
head in confusion---Wait, say that again?


Here's a quote from Bertrand Russell about philosophy (read: Haskell). He's 
actually being humorous, but it applies, in a way:


The point of philosophy is to start with something so simple as not to 
seem worth stating, and to end with something so paradoxical no one will 
believe it.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Something that kind of resembles OO

2010-07-09 Thread Michael Mossey
I notice in algebraic data defined with named fields, you can use the 
same name inside different constructors and then apply it to any data of 
that type.


data Vehicle = Car { ident :: String, wheel :: Circle }
 | Plane { ident :: String, stick :: Line }

f :: [Vehicle] - [String]
f = map ident

This is a little like fields in a base class.

I also see that a wrong use of accessor functions will compile but give 
a runtime error:


test = wheel (Plane foo (Line 1))

Will give a runtime error.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] use of modules to save typing

2010-07-08 Thread Michael Mossey
I'm fairly beginnerish to Haskell, and come from OO. I have a complaint 
about Haskell, but I think I found a good solution. Any suggestions welcome.


I have RSI and like to minimize typing. The use of classes as name 
spaces helps to do that. Also I can use some Emacs abbreviation magic 
easily with OO and not so easily with Haskell. I'll explain in a second.


In Haskell, when defining data for complex programs I like to use named 
fields to allow for changing data definitions without having to change 
all code. But named fields are top-level functions (I think). They must 
be chosen not to clash.


My habit has been to prefix them with the name of the constructor. So in 
a program for playing back musical documents that needs to track some 
state, we have:


data PlayState = PlayState
 { playState_cursor :: Int
 , playState_verts :: [Loc]
 , playState_len :: Int
 , playState_doc :: MusDoc
 }

Note all these playState_ prefixes. Lots of typing, which is not good.

In OO, you could type

   x.cursor()

In Haskell you have to type

   playState_cursor x

which also, I feel, is harder to read.

Now suppose I want to use PlayState with a State monad.

-- Increment the cursor.
incrCursor :: State PlayState ()
incrCursor =
  cur - gets playState_cursor
  len - gets playState_len
  let newCur = min (cur+1) (len-1)
  p - get
  put $ p {playState_cursor = newCur}

Okay, I'm sorry, that is just a lot of typing for what it is doing. Not 
good for people with RSI, and not all that readable.


I could define a function to make modifying the state a little easier.

playState_update_cursor :: Int - PlayState - PlayState
playState_update_cursor i p = p {playState_cur=i}

Then incrCursor would look like:

incrCursor :: State PlayState ()
incrCursor =
  cur - gets playState_cursor
  len - gets playState_len
  let newCur = min (cur+1) (len-1)
  modify (playState_update_cursor newCur)

Notice how often the characters playState_ get typed. This would be a 
great situation for Emacs abbreviations. When you define an abbreviation 
in Emacs, such as defining xps to expand to PlayState, emacs will 
watch for the characters xps. It will then replace xps with 
PlayState when you type a non-alphanumeric character following xps. 
So if I type xps. the moment I hit . it changes to PlayState.


But I would have a hard time using this feature with playState_ 
because it is always followed by an alphanumeric character.


So my idea, now, is to put the definition of PlayState in its own module 
and import it qualified as PlayState.


 module PlayState --

data PlayState = PlayState
   { cursor :: Int
   , verts :: [Loc]
   , len :: [Int]
   , doc :: MusDoc
   }

update_cursor i p = p {cursor = i}

---

I got rid of the playState_ prefixes because I am not worried about 
using generic field names like doc. They won't clash if I always 
import this qualified. And that reduces the necessary typing in the 
definition.


Now my monad looks like

testMonad = do
  cursor - gets PlayState.cursor
  len- gets PlayState.len
  let newCur = min (cur+1) (len-1)
  modify $ PlayState.update_cursor newCur

Now I can define an abbreviation for PlayState. This is a big help. 
Also, I find this more readable. To me


   PlayState.cursor

is more readable than
   playState_cursor

For one thing, syntax highlighting helps in the former case. For 
another, the latter case requires that you recognize a naming 
convention, but the former case says clearly: cursor is within the 
namespace PlayState, so this combination must be describing a cursor 
related to PlayState.






___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] use of modules to save typing

2010-07-08 Thread Michael Mossey



Michael Mossey wrote:

incrCursor :: State PlayState ()
incrCursor =
  cur - gets playState_cursor
  len - gets playState_len
  let newCur = min (cur+1) (len-1)
  modify (playState_update_cursor newCur)



Whoa, I just realized I'm not using 'modify' to full advantage. This can 
be written


incrCursor = modify incrCursor'
incrCursor' (PlayState cursor len verts doc) =
  PlayState (min (cursor+1)(len - 1)) len verts doc)

Hmm, I'm already feeling better about the State monad.

Additional question: what is proper terminology here?

incrCursor is a monad
incrCursor is a monadic function
incrCursor is a monadic type
State is a monad
State is a type constructor of a monad
State is a monadic type
incrCursor is a monadic computation

Thanks,
Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] use of modules to save typing

2010-07-08 Thread Michael Mossey



Neil Brown wrote:

On 08/07/10 09:08, Michael Mossey wrote:

data PlayState = PlayState
 { playState_cursor :: Int
 , playState_verts :: [Loc]
 , playState_len :: Int
 , playState_doc :: MusDoc
 }

Notice how often the characters playState_ get typed. This would be 
a great situation for Emacs abbreviations. When you define an 
abbreviation in Emacs, such as defining xps to expand to 
PlayState, emacs will watch for the characters xps. It will then 
replace xps with PlayState when you type a non-alphanumeric 
character following xps. So if I type xps. the moment I hit . it 
changes to PlayState.


But I would have a hard time using this feature with playState_ 
because it is always followed by an alphanumeric character.


What about auto-completion? 


Generally I prefer static abbreviations rather than dynamic expansion or 
auto-completion, because static abbreviations have predictable behavior.


I'm a bit obsessive-compulsive, so I get annoyed when, say, 
plexpand-key expands to something shorter than I expected. With static 
abbreviations, behavior is 100% predictable. The abbreviations I choose, 
like xps follow a convention so they are easy to remember. They have 
no capitals.


Plus the identifier before and after the period can be more generic and 
reusable, and in that case dynamic expansion is more reliable, or I'm 
more likely to benefit from defining a static abbreviation.


With that set of definitions, typing 
plexpand-key should give you playState_ (it expands to the longest 
unambigious expansion),


Hmm, when I use dabbrev-expand it expands to a complete identifier, but 
you can keep invoking it to rotate through all compatible identifiers. 
Maybe you are describing a mode I wasn't aware of.


I do use dabbrev-expand extensively, but once an identifier becomes very 
common I make a static abbreviation.


and adding cexpand-key should give you 
playState_cursor.  So you get the full thing for about five keystrokes, 
without any worrying about alphanumeric vs non-alphanumeric.


For example, as soon as I define playState_crunch then the behavior of 
dabbrev-expand changes. That's my complaint.




I have completion bound to tab in emacs (a la tab completion in the 
shell): (global-set-key (kbd TAB) 'dabbrev-expand) and am pretty 
happy with this for Haskell coding. 


Interesting, so you have abandoned it for indentation... but I guess 
typing spaces works okay. Or do you do something else?


 dabbrev-expand does not perform any
Haskell-specific context-sensitive completion -- it just picks words out 
of open buffers, but I've found this to work to my satisfaction.


It does work quite well. One of the most successful dumb algorithms I 
know.


Thanks,
Mike

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization in Haskell?

2010-07-08 Thread Michael Mossey



Daniel Fischer wrote:


If f has the appropriate type and the base case is f 0 = 0,

module Memo where

import Data.Array

f :: (Integral a, Ord a, Ix a) = a - a
f n = memo ! n
  where
memo = array (0,n) $ (0,0) : 
   [(i, max i (memo!(i `quot` 2) + memo!(i `quot` 3) 
 + memo!(i `quot` 4))) | i - [1 .. n]]


is wasteful regarding space, but it calculates only the needed values and 
very simple.


Can someone explain to a beginner like me why this calculates only the 
needed values? The list comprehension draws from 1..n so I don't 
understand why all those values wouldn't be computed.


Thanks
Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization in Haskell?

2010-07-08 Thread Michael Mossey
Thanks, okay the next question is: how does the memoization work? Each 
call to memo seems to construct a new array, if the same f(n) is 
encountered several times in the recursive branching, it would be 
computed several times. Am I wrong?

Thanks,
Mike

Gregory Crosswhite wrote:

 On 7/8/10 9:17 PM, Michael Mossey wrote:



Daniel Fischer wrote:


If f has the appropriate type and the base case is f 0 = 0,

module Memo where

import Data.Array

f :: (Integral a, Ord a, Ix a) = a - a
f n = memo ! n
  where
memo = array (0,n) $ (0,0) :[(i, max i (memo!(i 
`quot` 2) + memo!(i `quot` 3)  + memo!(i `quot` 
4))) | i - [1 .. n]]


is wasteful regarding space, but it calculates only the needed values 
and very simple.


Can someone explain to a beginner like me why this calculates only the 
needed values? The list comprehension draws from 1..n so I don't 
understand why all those values wouldn't be computed.




The second pair of each element of the list will remain unevaluated 
until demanded --- it's the beauty of being a lazy language.  :-)  Put 
another way, although it might look like the list contains values (and 
technically it does due to referential transparency), at a lower level 
what it actually contains are pairs such that the second element is 
represented not by number but rather by a function that can be called to 
obtain its value.


Cheers,
Greg

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] music-related problem

2010-07-05 Thread Michael Mossey



erik flister wrote:
 Michael Mossey wrote:


Regarding my use of Rational, it's because I'm representing
*notated* durations or positions in time, which are always fractions
of integers. Suppose I give the command to my program to play via
midi everything from bar 1 beat 1 to bar 2 beat 2 1/2. I want to use
Rational so I know 2 1/2 means 2 1/2 and not 2.499. 



i wasn't suggesting anything Numeric for durations -- those are NoteDurs 
like (Dotted $ Triplet Half).  you don't need numerics until resolving 
temporal locations, like milliseconds or subdivisions of a beat.  those 
may be irrational numbers (consider if the tempo is irrational, or tiny 
random jitter in timing) -- though it's a totally pedantic point on my 
part and realistically won't matter.  ;)
 


We must be addressing different problems. My software doesn't have much 
interest in the concept of eighth notes or dotted notes.


What I want to do is process a musical document to answer questions like this:

  - what notes have onset times between measure 1 beat 1 and measure 1 beat 3?

  - organize the document into verticals: notes that occur at the same 
time in any part


  - what notes finish sounding before measure 4?

In music, the passage of time has two meanings. One meaning is provided by 
the notation: on what beats notes occur and how they last (in terms of 
beats). This is independent of tempo, rit, accel. Call this score time. 
The other meaning is real-world performance in which tempo, rit, accel, 
trills and tremolos are realized. Call this real time.


For the first meaning, my program will find it simple and useful to 
represent time as measure (Int) and beat (Rational --- or perhaps anything 
in class Fractional (I have to study this more)). If I tried to represent 
score time as eighth notes or whatever it would drive me crazy. I have no 
need to do that. (Note that this level of time representation is not 
intended for a human interface.)


Score time can involve fractions composed from numbers greater than 
four---like 7-tuplets. But to my knowledge, there is no way to notate 
something that cannot be represented by a fraction.


Real time is better represented as floating point. It is derived from 
tempos and tempo maps.


Thanks,
Mike





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] emacs tags

2010-07-05 Thread Michael Mossey
(I asked this question on the logical email list to ask, haskell-mode, but 
got no reply, so I'm hoping someone here might know the answer.)


I tried to use tags with emacs.

I ran :etags in ghci, then tried to use C-c M-. inside Emacs
to find the definition of a symbol. It reported no source information
available. I did some basic checking---a TAGS file does exist in the same 
directory as the file I was visiting, and contains some kind of entry for 
the specific symbol (whether the right syntax I don't know).


I'm using haskell-mode 2.4 and emacs 21.3.1 on Windows XP. Also ghci 6.12.1.

Thanks,
Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] music-related problem

2010-07-04 Thread Michael Mossey

Wondering if I could get some suggestions for coding this problem.

A musical document (or score) consists primarily of a list of measures. A 
measure consists primarily of lists of items. We'll consider only one 
kind of item: a note. Items have a location within the measure. A note's
location indicates both where it goes on the page (i.e. a visual 
representation of the score) and what moment in time it begins sounding 
(i.e. rendering the score in sound). My concern here is sound.


data Doc = [Measure]

data Loc = ... (represents a location within the musical
document including measure number)


data Measure = Measure [(Loc,Item)]
  -- In the Meausre, we can assume (Loc,Item) are in
  --  ascending order


Notes also have an end, when indicates when in time they stop
sounding. See the 'end' field below. Also note the 'soundedEnd'
 'tieStart' and 'tieStop' fields which I will explain.

data Item = Note
{ pitch :: Pitch
, end :: Loc
, soundedEnd :: Maybe Loc
, tieNext :: Bool
, tiePrior :: Bool
}

There is a concept of tied notes. When two notes are tied
together, their durations are summed and they are sounded
continuously as if one note. Ties have several uses, but one
important one is to make a sound that begins in one measure and
ends in a later measure, by tying notes across measures.

The 'tieNext' field indicates if a note is tied to the following
note (that is, the next note of the same pitch). 'tiePrior'
indicates if tied to immediately prior note of same pitch.

A chain of notes can be tied. Notes in the middle with have
both tieNext and tiePrior set.

In the event a note is within a chain of ties, its 'soundedEnd'
field needs to be computed as Just e where e is the end of the
last note in the chain. This information is useful when rendering
the document as sound.

My problem is:

  - given a Doc in which all fields have been set EXCEPT soundedEnd
(all soundedEnd's are given a default value of Nothing)
  - update those notes in the Doc which need to have soundedEnd set.
This involves chasing down the chain of ties.

I can solve a simpler problem which is

-- Given a note with tieNext set, and a list of notes, find
-- the end Loc of the last note in the chain. Only notes
-- with the same pitch as 'firstNote' are considered when looking
-- for the chain of notes.
computeSoundedEnd :: Item - [Item] - Loc
computeSoundedEnd firstNote notes = compSndEnd (pitch firstNote) notes

compSndEnd :: Pitch - [Item] - Loc
compSndEnd _ [] = error tie chain doesn't come to completion
compSndEnd p (n:ns) = if pitch n == p
then if tieNext n
  then if tiePrior n
then compSndEnd p ns
else error illegal tie chain
  else if tiePrior n
then end n
else error illegal tie chain
else compSndEnd p ns

The thing that is hard for me to understand is how, in a functional
paradigm, to update the entire Doc by chasing down every tie and making
all necessary updates.

Thanks,
Mike








___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Michael Mossey



Henning Thielemann wrote:


On Sun, 4 Jul 2010, Michael Mossey wrote:


I can solve a simpler problem which is

computeSoundedEnd :: Item - [Item] - Loc
computeSoundedEnd firstNote notes = compSndEnd (pitch firstNote) notes


You will certainly not be able to make use of foldl or foldr, but you 
may use a manual recursion instead. Just like


computeAllEnds :: [Item] - [Item]


What makes it harder than this is that the original document is not a 
single list of Item's--they are broken into measures.


Thanks,
Mike

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Michael Mossey



Serguey Zefirov wrote:

The thing that is hard for me to understand is how, in a functional
paradigm, to update the entire Doc by chasing down every tie and making
all necessary updates.


This looks like one of graph algorithms.

Notes are nodes, ties are arcs. Measures, etc are parts of node label.

soundedEnd property can be computed over this.

Actually, it would be wise to parametrize Item with computed
attributes so that you can clearly distinguish between documents where
soundedEnd is set from documents where it is not.


Ah, this sounds like something I am looking for... parameterizing Item with 
the computed attributes. But I am not clear about what that would look 
like. Would Item have kind * - *? Like


data Item c = Item {pitch::Pitch, end::Loc, computed::c}

?

Thanks,
Mike

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Michael Mossey

Hi Stephen,
Thanks for thinking about this. The problem, though, is that notes can 
overlap in time. MusicXML solves this by having not just Note and Rest, but 
Backup and Forward which indicate the current position should be moved 
before interpreting the following data. I'm trying to make it simpler than 
that, by giving a note an absolute location and duration.


-Mike

Stephen Tetley wrote:

If you add Rest as an alternative constructor to Item you should be
able to attribute Items with their duration rather than their onset
position. For most processing this would simplify things.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Michael Mossey



Henning Thielemann wrote:


On Sun, 4 Jul 2010, Michael Mossey wrote:


Henning Thielemann wrote:


On Sun, 4 Jul 2010, Michael Mossey wrote:


I can solve a simpler problem which is

computeSoundedEnd :: Item - [Item] - Loc
computeSoundedEnd firstNote notes = compSndEnd (pitch firstNote) notes


You will certainly not be able to make use of foldl or foldr, but you 
may use a manual recursion instead. Just like


computeAllEnds :: [Item] - [Item]


What makes it harder than this is that the original document is not a 
single list of Item's--they are broken into measures.


That is, you want a function of type

computeAllEnds :: [Measure] - [Measure]

?


Right, although it occurs to me that it might be superior to represent the 
document as [Item] and give Item a measure-number attribute. There are also 
other measure attributes, so in that case the doc would look like:


data Doc = Doc [MeasureInfo] [Item]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Michael Mossey



erik flister wrote:
ties are a presentation-level issue, the underlying (sound) 
representation is a single note.  i suggest


Doc = [Note]

where Notes have fields for their measure location and duration.  then 
there's no issue with overlapping notes, and start/end times are easy to 
calculate.  ties can be calculated easily later for graphical layout by 
asking if durations overlap given boundaries (usually measure 
boundaries, but also measure centers).



Hi erik,
I will look at your EDSL. However, I am dealing with ties because I am 
converting a MusicXML document into a more natural form for my purposes. 
The initial form of the document will have tied notes (as it comes that way 
from MusicXML), and I want to convert that into a form that makes it 
possible to ignore ties and see notes as having a single duration.


Thanks,
Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Michael Mossey



erik flister wrote:

I am dealing with ties because I am converting a MusicXML document
into a more natural form for my purposes. The initial form of the
document will have tied notes (as it comes that way from MusicXML),
and I want to convert that into a form that makes it possible to
ignore ties and see notes as having a single duration.


but can't you just say that the first note of a tie has the indicated 
start time and a duration which is the sum of the tied notes?  i don't 
know musicXML, but i'm not seeing why that would be hard...


That's what I want to do. I'm asking about a good way to write the 
algorithm that traverses the notes and reconstructs the document with the 
correct duration in each note. Actually, I don't want to lose information 
about the original form of the document, so I have separate fields for the 
duration of the graphical single note, and the duration of the tied chain.


Actually, it is better to speak of the end time than the duration, because 
what units do you put duration in? Beats? The time signature could be 
changing measure to measure. MusicXML position? The meaning of one 
position changes measure to measure and can be different in different 
parts. It can get confusing. So I use this concept of location:


data Loc = Loc Int Rational   -- measure number and beat within the measure

I.e. measure 1, beat 2
 measure 7, beat 3 1/2

I use Rational so there is no worry about precision of Floats.

Thanks,
Mike



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Michael Mossey



erik flister wrote:


That's what I want to do. I'm asking about a good way to write the
algorithm that traverses the notes and reconstructs the document
with the correct duration in each note. 



why isn't this as simple as 


Erik,
I'm learning from your code examples, but I don't understand how this 
turned into an argument about simplicity. I never said it was complex. I do 
admit it's probably simpler than my initial approach.


Maybe I should take a step back and describe my goals. I am experimenting 
with algorithms for putting a human touch on midi playback. I will use 
Finale to enter the music, then export as MusicXML to my software. Getting 
from MusicXML---which is a complex format that encompasses everything from 
notational subtleties to performance subtleties---into a relatively simple 
internal representation is truly the easy part. The real meat of my project 
is the code to perform the music.



foldr'ing something like this over the xml 
notes (assuming monophony and that they are listed in order of start time)?


In a MusicXML document, you can't assume

  - that the notes are in order of start time
  - monophony
  - that two tied notes are immediately adjacent in the data

None of that is true. I conceive of this problem as multiple passes. On the 
first pass, I translate XML notes into a convenient internal 
representation, on the second pass sort them, then make a pass to figure 
out ties. Whether this is the best approach, I do not know. I am here to learn.


Regarding my use of Rational, it's because I'm representing *notated* 
durations or positions in time, which are always fractions of integers. 
Suppose I give the command to my program to play via midi everything from 
bar 1 beat 1 to bar 2 beat 2 1/2. I want to use Rational so I know 2 1/2 
means 2 1/2 and not 2.499. (*) However, *performed* times are a 
matter of tempo, accel, rit, trills, tremolo, arpeggio etc., and are 
probably best conceived as Real.


I don't quite get this:

 forall x. (Real x, Fractional x) = x if you're picky.

Thanks,
Mike

(*) I may want to use the location of a note (bar and beat) as the key in a 
Map, which I believe should be done with Rational and not Float.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] seems like I'm on the wrong track

2009-12-02 Thread Michael Mossey



Stephen Tetley wrote:

Hi Mike

There used to be some slides available commenting on Haskore's CSound
interface. But they seem to have vanished (I have a copy rendered to
pdf when they were available). Like all slide presentations there's a
lot of reading between the lines to get a good picture after the fact:


http://www.nepls.org/Events/16/abstracts.html#hudak
http://plucky.cs.yale.edu/cs431/HasSoundNEPLS-10-05.ppt  -- vanished



This looks like a great resource. Maybe Dr. Hudak can get me a copy. He 
clearly has the experience to implement a CSound compiler as gracefully 
as anyone could.




Maybe you're doomed to frustration though trying to implement your
system in Haskell. For the argument I'm about to make, I'd say a
working programming language has two things - syntax, semantics and
libraries and a repertory of prior art. Stateful programming clearly
has some syntax burden in Haskell, stateful monadic programming has
some benefit of 'stratification' - you have precise control of 'what
state is where'. It's a matter of taste whether you like Python's
flexibility or Haskell's, erm, 'locality' (precision?).

As for the second half of what you get from a programming language,
your system description frames what you want to do with an emphasis on
dynamic aspects. This seems a good way off from the prior art in
Haskell. For instance there are Haskell synthesizers - George
Giorgidze's yampa-synth and Jerzy Karczmarczuk's Clarion (actually in
Clean, but near enough). Here you build signal processing modules -
unit generators, of course - Yampasynth uses arrows to do this Clarion
uses infinite streams. With both you would build a synthesizer
statically from unit generators and somehow run it to produce
sounds[1].

There is also the prior art of embedded hardware description
languages, Lava, Hydra, Wired, Gordon Pace's HeDLa, soon Kansas Lava.
One could view constructing synthesizers from unit generators as
usefully analogous to constructing circuits - and certainly if you are
'compiling' to another system to do do the real work (in your case
CSound) the papers on Wired, HeDLa, and Kansas Lava have useful
insights on 'offshoring' compilation. But again these systems have
strong bearing in the 'static description' of a circuit rather than
its dynamical operation.



Thanks for this detailed review. I will investigate these things.

My system sits halfway between a low-level signal processor language like 
CSound and a high-level music description language like Hudak's Haskore. My 
work as a composer will be done at the highest level possible, which means 
thinking in terms of notes---things that go boo at a certain time, 
place, frequency, amplitude, timbre, etc. But I want to express things 
beyond, say, MIDI, like indicating that a group of notes should be played 
legato---which doesn't mean play them individually with no separation of 
notes but actually means modify the csound instrument's behavior at the 
time of note connections. So in one small breath I can say, Make this 
legato and at the low level the elves are scurrying around like mad, 
rearranging code, changing out instruments, merging notes, etc.


I also have a bad case of Not Invented Here Syndrome---seriously, I want 
to use this system to do experimental composition, by which I mean any 
crazy idea I dream up can be implemented by adding to or modifying my 
system, which gives me a preference to write it myself.



If neither of those 'genres' is close to what you really want to do
then the Haskell prior art is running a bit thin. You could look at
dataflow - the dynamic PD / Max systems are often describe as a
dataflow systems. There are some outposts in Haskell of dataflow
programming - Gordon Pace has an embedding of Lustre available from
his homepage and there has been work on dataflow programming via
comonads. There is also reactive programming, but musical examples are
thin on the ground
(nonexistent?) so it might be a long haul to come up with something.



But this all sounds great to study.

Thanks,
Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] seems like I'm on the wrong track

2009-12-02 Thread Michael Mossey

Hi Gregg,

Yes, I've read his book School of Expression and I'll have to check up on 
this draft.


His ideas are very useful at the level of composing music, where an 
algebraic representation is natural and flies free and high. It's when that 
representation grinds against an old quaint system like CSound that things 
get ugly. However, I have a new idea. Stay tuned.


-Mike

Gregg Reynolds wrote:
On Tue, Dec 1, 2009 at 7:55 PM, Michael Mossey m...@alumni.caltech.edu 
mailto:m...@alumni.caltech.edu wrote:
  Thanks for the reply. Was there something specific you were referring 
to, or


Maybe http://plucky.cs.yale.edu/cs431/reading.htm Chapter 9 An Algebra 
of Music.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] seems like I'm on the wrong track

2009-12-02 Thread Michael Mossey



Michael P Mossey wrote:
Perhaps someone could either (1) help me do what I'm trying to do, or 
(2) show me a better way.


I have a problem that is very state-ful and I keep thinking of it as OO, 
which is driving me crazy. Haskell is several times harder to use than 
Python in this instance, probably because I'm doing it wrong.




Stop the presses! I had an idea to make this more functional in style. Do 
it through multiple passes.


The idea is that we've got a list of musical events as input (Node is a 
term some algorithmic composers use, so I will use type Node.)


In fact we could have other types of input data too, so I might need the 
algebraic type


data InputType = Node ...
   | CSoundSource ...

etc.

Then we make a pass through the nodes using map concat to produce a bunch 
of Output data.


data Output = OIStatement ...
| OInstrName InstrName  -- represents an instrument name
-- (ultimately we need a number, but
--  won't know that # during first
--  pass)
| OInstrNum Int -- when we compute an instrument
-- number, this will replace the above
| OMixer MixerName
 ...

we have a function processInput:

processInput :: InputType - [Output]

This expresses the idea that a single input may result in the generation of 
several pieces of output data.


The first pass is just a concat map

firstPass :: [InputType] - [Output]
firstPass = concatMap processInput

In translating an InputType datum, we look at it in isolation---here it 
sits in front of us in the stream, and we haven't maintained a lot of 
state---and we translate it to some intermediate Output form, making all 
specific calculations or substitutions possible at that given time and context.


Then further passes are needed, many of which are folds. For example, to 
assign the instrument number I have some kind of NumberDatabase, but now my 
dealings with it are limited to a single fold.

assignNumbers :: [Output] - NumberDatabase
assignNumbers outputList = foldl g newNumberDatabase outputList
  where g outputDatum numberDb =
   case outputDatum of
  OInstrName n - ... ah! unassigned name! update db
  _- numberDb  -- just return unchanged


All the rest of the processing can be done via filters, folds, and maps.

Does this seem more functional in style?

Thanks,
Mike



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] seems like I'm on the wrong track

2009-12-01 Thread Michael Mossey
Thanks for the reply. Was there something specific you were referring to, 
or just the idea that he wrote Haskore? Haskore is not very closely related 
to what I'm trying to do. I believe he has a CSound back end for Haskore, 
but it is in a rough state and not closely related to what I'm trying to 
do. Most computer music packages have a fairly well-defined idea of a 
musical event, and events usually get translated one-to-one into another 
language. I have a quite messy problem which is describable as a big state 
machine, at least in the way I think of it. An input event can trigger a 
cascade of changes to the state. Channel numbers must be assigned and 
tracked, table numbers as well, decisions about whether to create a new 
table or re-use an old one, global variables and commands added and/or 
modified, etc. So I am hoping for a comment from that perspective.


Thanks,
Mike

Casey Hawthorne wrote:

Please check out Paul Hudak's page.

http://cs-www.cs.yale.edu/homes/hudak-paul/


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] seems like I'm on the wrong track

2009-12-01 Thread Michael Mossey



Daniel Fischer wrote:

getNumber :: String - AssignedNumbers - (Int,AssignedNumbers)


Yeah, that screams State Monad.



Hi, thanks for all the advice.

I was hoping my AssignedNumbers class would be useful with many data 
structures. In other words I would have


data State1 = State1 { a :: AssignedNumbers, b :: AssignedNumbers, ... }
data State2 = State2 { c :: AssignedNumbers, d :: AssignedNumbers, ... }

func1 :: State State1 Int
func1 = do
   ... something using a and b ...

func2 :: State State2 Int
func2 = do
   ... something using c and d ...

So I thought maybe I could defined a function like

nextNumber :: MonadState s m = (s - AssignedNumbers) - (AssignedNumbers 
- s) - m Int

nextNumber retreive putBack = ...

and have it be useful in both State State1 a and State State2 a monads, 
but defining the retrieve and putBack functions isn't pretty.


I will try to grok Robert's reply also. Maybe he has something addressing this.

Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] I miss OO

2009-11-25 Thread Michael Mossey
I'm fairly new to Haskell, and starting to write some big projects. 
Previously I used OO exclusively, mostly Python. I really miss the 
namespace capabilities... a class can have a lot of generic method names 
which may be identical for several different classes because there is no 
ambiguity.


In my musical application, many objects (or in Haskell, data) have a time 
associated with them. In Python I would have an accessor function called 
time in every class.


So if I have objects/data note1, cursor1, and staff1,

Python:
  note1.time()
  cursor1.time()
  staff1.time()

Haskell needs something like
  note_time note1
  cursor_time cursor1
  staff_time staff1

which is a lot more visually disorganized.

What's worse, I have a moderate case of RSI (repetitive strain injury) so I 
type slowly and depend on abbreviations a lot. I use the souped-up 
abbreviation capabilities of Emacs. Let's say I have a 
field/member-variable called orientedPcSet that is used across many 
classes. In Python, I can create an abbreviation for that and it is useful 
many times. In Haskell, I might need


someType_orientedPcSet
someOtherType_orientedPcSet
thirdType_orientedPcSet

which prevents me from using abbreviations effectively (especially the 
dynamic-completion feature). (It would help to make the underscore not part 
of word syntax, but that's not ideal.)


So I'm thinking of moving to a scheme in Haskell using modules, most types 
being defined in their own modules, and doing qualified imports. Generic 
names like 'time' can be defined in each module w/o clashing. Then I have


Note.time note1
Cursor.time cursor1
Staff.time staff1

This is very useful because I can define abbreviations for the type name 
and for oft-used accessor function names and these abbrevs are more 
organized, easier to remember, and easier to combine.


I would be interested in comments... is this a good way to do things? Am I 
trying too hard to impose OO on Haskell and is there a better way?


Thanks,
Mike

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] I miss OO

2009-11-25 Thread Michael Mossey
First of all, thanks for the ideas, everyone. I think I'm starting to get 
the usefulness of type classes.


With regard to your question, Eugene, you are probably right. In fact my 
rough draft of this code from four months ago used a Map with time as the 
key (of type Rational). I was trying to come up with a quick example and 
didn't think straight.


You may observe, however, that the concept note has a lot of uses and 
contexts. Sometimes it means simply a pitch, like middle C. Sometimes it 
means a black dot on a piece of staff paper, in which case it has a 
duration (as a number of beats). The context of that black dot gives it a 
dynamic level, an associated instrument (timbre), and of course, a time. In 
this larger context, I'm not sure if there is a deep difference between 
storing time inside the object or outside it, except for the practical 
matter of wanting to index notes by time (in which case it is useful to use 
time outside the object as the key). You tell me: do you think it makes a 
deep difference?


Thanks,
Mike


Eugene Kirpichov wrote:

Hi,

Are you sure you need to store the time *inside* your objects
instead of using, say, pairs (Time, YourObject) (and lists of them
instead of lists of your objects)?
It would seem strange to me that a note HAS-A time even in an OO
design: more likely, a note is associated with a time, and this is
modeled by pairing them.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] help with musical data structures

2009-11-15 Thread Michael Mossey

Hi Stephen,

I will need a function that computes prime (normal?) form, of course, and 
it is just begging to be memoized. I wonder if that is possible with 
Data.Set, or whether it would be much faster using the bit vector 
representation?


Thanks,
Mike



Stephen Tetley wrote:

Postscript...

Hi Mike

I rather overlooked your efficiency concerns, however I wouldn't be so
concerned. By the nature of what they represent I wouldn't expect
pitch classes to grow to a size where a bit representation out weighs
the convenience of a list or Data.Set.

By the same reason - I'd only use an array for the pitch matrix if I
felt an interface favouring index-lookup was most 'comfortable'.



Best wishes

Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] O(n) algorithm for determining subset

2009-11-15 Thread Michael Mossey
Can someone tell me if this is correct. I'm guessing that if I represent
two sets of integers by Word32 (where ith bit set means i is in the set),
then an algorithm to determine if x is a subset of y would go something
like


  (y - x) == (y `exclusiveOr` x)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] help with musical data structures

2009-11-14 Thread Michael Mossey
I'm pretty new to Haskell so I don't know what kind of data structure I
should use for the following problem. Some kind of arrays, I guess.

One data item, called OrientedPCSet (oriented pitch class set, a musical
term) will represent a set whose members are from the range of integers 0
to 11. This could probably be represented efficiently as some kind of bit
field for fast comparison.

Another item, PitchMatrix, will be a 2-d matrix of midi pitch numbers.
This matrix will be constructed via a backtracking algortithm with an
evaluation function at each step. It will probably be constructed by
adding one number at a time, starting at the top of a column and working
down, then moving to the next column. This matrix should probably be
implemented as an array of some sort for fast lookup of the item row x,
column y. It doesn't require update/modification to be as fast as lookup,
and it won't get very large, so some sort of immutable array may work.

Thanks,
Mike



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] multi-line regex

2009-11-03 Thread Michael Mossey
I have some very simple regex-matching needs, and Text.Regex.Posix will 
work fine, EXCEPT I need to match multi-line patterns, and/or find all 
occurrences of text that may occur several times on different lines. So I 
need to turn on some kind of flag. Can someone show me how to do that? I 
have worked the examples in RWH so I basically know how to run the thing.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] multi-line regex

2009-11-03 Thread Michael Mossey



kenny lu wrote:

Hi Michael,

Could you give an example of what patterns you want to write?

Regards,
Kenny



Something like

text = 11\n abcd \n22
answer = text =~ 11.*22 :: various possibilities

and have it find the entire string. The default behavior is to stop 
matching when it encounters a newline. There is mention in the 
Text.Regex.Posix docs of a flag to control this behavior, but it is not 
easy to figure out from the docs how to provide flags. The left-hand side 
of the =~ is a very complex type.





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] tips on installing System.Console.Readline

2009-10-26 Thread Michael Mossey
Before I ask my main question, incidentally has anyone noticed that the 
GHCI prompt, on Windows XP, now has auto-completion! (since 6.10) Awesome!


I'm trying to install System.Console.Readline on Windows XP. I need to have 
GNU readline installed first, which I did (by multiple methods). But 
running 'cabal install readline' it reports that readline is not found. 
Obviously I need to set a path or environment variable... can anyone help?


Thanks,
Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Real World Haskell Chapter 19 and GHC 6.10

2009-10-21 Thread Michael Mossey
The examples in the error handling chapter (19) of RWH don't run under 
GHC 6.10.


For instance, an example might be

main = handle (\_ - putStrLn error) (print $ 5 `div` 0)

Trying to load this results in amigous type variable 'e' in the 
constraint: 'Exception e' arising from a use of 'handle' etc etc.


I was able to fix this via the ludicrously complex:

main2 = (handle :: (SomeException - IO ()) - IO () - IO ())
(\_ - putStrLn Error calculating result)
(print $ 5 `div` 0)

Is there a more concise way to use handle, or can someone point me to a 
tutorial that might explain the changes in 6.10 and in a general way how to 
get the RWH examples to run?


Thanks,
Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Real World Haskell Chapter 19 and GHC 6.10

2009-10-21 Thread Michael Mossey
Apparently the old exception library had convenience functions like 
'arithExceptions' that could be used with 'handleJust'.


handleJust arithExceptions handler thing

With the new module you can write something like this (I determined this 
from experimentation):


arithExceptionTester :: ArithException - IO ()
arithExceptionTester = Just ()

handleJust arithExceptionTester handler thing


Two questions:

(1) Is there a better way to do things?

(2) I don't understand quite how the type system works. Somehow, on 
exceptions that aren't arithmetic, arithExceptionTester returns Nothing or 
at least behaves that way. Yet I didn't write any code to do that. Can 
someone explain this?


Thanks,
Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] example of PortMidi use

2009-10-14 Thread Michael Mossey
Can someone give me an example of Sound.PortMidi use? I'm having trouble. 
This program has bugs---makes sound only intermittently, and seems to have 
set up some kind of loop that is sending midi messages continuously even 
after terminating the program:


import Sound.PortMidi
import Foreign.C

msgs = [ (0::CULong,PMMsg 0x9c 0x40 0x40)
   , (500,  PMMsg 0x8c 0x40 0x40)
   , (1000, PMMsg 0x9c 0x41 0x40)
   , (1500, PMMsg 0x8c 0x41 0x40) ]



main = do
  let deviceId = 12
  initialize = print
  getDeviceInfo deviceId = print
  startTime - time
  let evts = map (\(t,msg) - PMEvent msg (t+startTime)) msgs
  result - openOutput deviceId 10
  case result of
Right err   - putStrLn (After open:  ++ show err)
Left stream -
do result - writeEvents stream evts
   putStrLn (After write:  ++ show result)
   close stream
   return ()
  terminate = print

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] statistics package and randomness

2009-10-12 Thread Michael Mossey
I'm trying to learn how to use randomness in Haskell and it seems very 
non-straightforward and complex. I could do a lot of things using 'split' 
from System.Random, but apparently it's broken. There is the statistics 
package here:


http://hackage.haskell.org/package/statistics

Is this a better solution?

It uses the ST monad in the RandomVariate module. Can someone point me to a 
tutorial explaining ST, and/or a tutorial in the RandomVariate module?


Pseudorandomness seems like one case where it would just be a hell of a lot 
simpler to have a global generator--never split the state. Is the ST monad 
some way to accomplish this?


Thanks,
Mike


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] safe way to use Rand?

2009-10-12 Thread Michael Mossey
I'm looking at Control.Monad.Random which provides the Rand monad. I would 
like to know how to use this for generating multiple infinite series, while 
trusting that the implementation never uses split behind the scenes.


(Note: I'm on Windows XP, and there appears to be a bug in getStdGen. It 
does NOT return an arbitrary generator, but rather the same one every time 
I run the program. However, newStdGen DOES return an arbitrary generator. 
So I'm using that, even though I know it accesses split behind the scenes. 
My thinking is that this only happens once so it is okay.)


For example, is this code split-free?

simple :: Rand StdGen [Int]
simple = getRandomRs (0::Int, 10)

main1 = do
   gen - newStdGen
   let answer = (flip evalRand) gen $ do
  xs - simple
  ys - simple
  return $ (take 5 xs) ++ (take 3 ys)
   print answer

Then, to elaborate on my specific problem, I need to create special types 
of infinite series. For example, I might need to create one that looks like 
this:


0 0 5 0 0 0 2 0 0 0 0 0 5 0 9 0 0 8 ...

The pattern here is that there is some random number of zeros followed by a 
single non-zero value, followed again by a random number of zeros, etc. 
forever.


This is one way to implement this. Does all look well here?


makeSeries :: [Int] - [a] - a - [a]
makeSeries (i:is) (f:fs) zero = replicate i zero ++ [f]
++ makeSeries is fs zero

lessSimple :: Rand StdGen [Int]
lessSimple = do
  counts - getRandomRs (1::Int  , 5  )
  values - getRandomRs (1::Int  , 9  )
  return $ makeSeries counts values 0

main2 = do
   gen - newStdGen
   let answer = evalRand lessSimple gen
   print . take 20 $ answer

We could even have several of these series zipped together. Is this split-free?

main3 = do
  gen - newStdGen
  let fs = (flip evalRand) gen $ do
 s1 - lessSimple
 s2 - lessSimple
 return $ zip s1 s2
  print . take 20 $ fs


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] more improvable randomness

2009-10-08 Thread Michael Mossey
I wrote some code to model the keystroke-to-keystroke delay in a person
typing, with pseudorandomness. There are two kinds of delays.. one is a
very small delay as the person reaches for a new key (call this 'reach'
delays), the other is a larger delay that represents a pause to think or
to take a break (call this 'break' delays).

My thought is that I could create an infinite series of reach delays and
an infinite series of break delays and zipWith (+).

The inifinite series of break delays would look like:

- The overall pattern is a large number of zeros, in the range (N,M)
followed by a single positive number, chosen from a distribution D... and
then repeat.

Here's some code. I used the Gen monad to gain access to the 'frequency'
function, which is useful, but I had trouble figuring out how to put the
whole algorithm into Gen. I also looked at Rand. The problem is that if I
want to create the list by 'sequence'ing a list of monads, they need to
have state that remembers how many zeros are left to go.



breakSeries :: Int - Int - StdGen - [Float]
breakSeries lowerB upperB gen =
   let (n,gen1) = randomR (lowerB,upperB) gen
   (gen2,gen3) = split gen1
   delay = generate 1 gen2 breakM
   in replicate n 0 ++ [delay] ++ breakSeries lowerB upperB gen3

breakM :: Gen Float
breakM = frequency [ (10, choose( 1::Float   ,  2))
   , (10, choose( 4::Float   ,  6)) ]

test = (print . take 100 . breakSeries 2 4 ) = newStdGen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] random question

2009-10-07 Thread Michael Mossey
My thread about randomness got hijacked so I need to restate my remaining 
question here. Is it acceptable to write pure routines that use but do not 
return generators, and then call several of them from an IO monad with a 
generator obtained by several calls to newStdGen?


shuffle :: RandomGen g = g - [a] - [a]
shuffle = ...

foo :: [a] - [a] - IO ()
foo xs ys = do
  g1 - newStdGen
  print $ shuffle g1 xs
  g2 - newStdGen
  print $ shuffle g2 ys

Does this kind of thing exhibit good pseudorandomness?

Thanks,
Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] random question

2009-10-07 Thread Michael Mossey



Luke Palmer wrote:

On Wed, Oct 7, 2009 at 2:59 PM, Michael Mossey m...@alumni.caltech.edu wrote:

My thread about randomness got hijacked so I need to restate my remaining
question here. Is it acceptable to write pure routines that use but do not
return generators, and then call several of them from an IO monad with a
generator obtained by several calls to newStdGen?


It's gross.  What if you don't want IO as part of this computation?



I don't quite follow your response. I want a program that initializes the 
generator from the global generator because I want different behavior every 
time I run it. So it will need IO. That's what I was trying to demonstrate. 
And I was wondering if one can get around the difficulty of passing the 
generator from call to call by using newStdGen in this way.


Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Test.QuickCheck: generate

2009-10-07 Thread Michael Mossey
In Test.QuickCheck, the type of 'generate' is

generate :: Int - StdGen - Gen a - a

I can't find docs that explain what the Int does. Some docs are here:

http://www.haskell.org/ghc/docs/latest/html/libraries/QuickCheck/Test-QuickCheck.html

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] better way to do this?

2009-10-05 Thread Michael Mossey



Eugene Kirpichov wrote:

[x,y,t,b,l,r] - mapM (getStdRandom . randomR) [(-10,10), (-70,70), ...]
return (BoxBounds ...)


Thanks.

I'm curious about the idea of pattern matching in do-statements that can 
fail. This particular pattern cannot fail. I read that the fail function 
was introduced to Monad in order to handle pattern matches that fail, and 
that most members of haskell-cafe seem to think that was a mistake---that 
MonadZero should have been used instead. I.e., any do-block with a pattern 
that can fail should explicitly have a MonadZero class constraint.


This leads to my question about detecting pattern matches that could fail. 
We can easily prove the above pattern will never fail. I'm wondering if the 
compiler infers this. And if a future version of Haskell dumps fail and 
used MonadZero to replace it, would that future Haskell compiler need to 
infer, in all cases, whether a pattern can fail? Is it simple enough to 
make that correct inference?


Thanks,
Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] better way to do this?

2009-10-05 Thread Michael Mossey
If I understand correctly, this works because IO is an instance of 
Applicative, correct?


I wonder if any of the random monads are instances of Applicative.

Felipe Lessa wrote:

On Sun, Oct 04, 2009 at 01:55:11PM +0400, Eugene Kirpichov wrote:

[x,y,t,b,l,r] - mapM (getStdRandom . randomR) [(-10,10), (-70,70), ...]
return (BoxBounds ...)


import Control.Applicative

let f = getStdRandom . randomR
g1 = \x - f (-x,x)
g2 = f (5,10)
in BoxBounds $ g1 10 * g1 70 * g2 * g2 * g2 * g2

--
Felipe.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] apply function arguments in a list

2009-10-05 Thread Michael Mossey
If I have a list containing the arguments I want to give to a function, is 
there a general way to supply those arguments in a compact syntax?


In other words, I could have

args = [1,2,3]
f x y z = ...

I would write

t = f (args!!0) (args!!1) (args!!2)

but there may be a neater, more general syntax. I tried writing a fold with 
$, but I don't think that works because the type of each step is different. 
I.e.


f :: a - a - a - a
f x :: a - a - a
f x y :: a - a
f x y z :: a

This would seem to preclude a general way of writing a function that 
supplies arguments from a list.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] better way to do this?

2009-10-04 Thread Michael Mossey
I'm looking for a hint to write the following code with less redundancy. I
have a constructor called BoxBounds, and I want to make one with random
values.

randomBox :: IO BoxBounds
randomBox = do
  x - getStdRandom (randomR (-10,10))
  y - getStdRandom (randomR (-70,70))
  t - getStdRandom (randomR (5,10))
  b - getStdRandom (randomR (5,10))
  l - getStdRandom (randomR (5,10))
  r - getStdRandom (randomR (5,10))
  return (BoxBounds x y l r t b)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] better way to do this?

2009-10-04 Thread Michael Mossey



Duncan Coutts wrote:

On Sun, 2009-10-04 at 02:52 -0700, Michael Mossey wrote:

I'm looking for a hint to write the following code with less redundancy. I
have a constructor called BoxBounds, and I want to make one with random
values.

randomBox :: IO BoxBounds
randomBox = do
  x - getStdRandom (randomR (-10,10))
  y - getStdRandom (randomR (-70,70))
  t - getStdRandom (randomR (5,10))
  b - getStdRandom (randomR (5,10))
  l - getStdRandom (randomR (5,10))
  r - getStdRandom (randomR (5,10))
  return (BoxBounds x y l r t b)


Others have already answered but I'd like to suggest that you avoid
using IO here. There's no need for this to be impure. The getStdRandom
function is one that should be avoided IMHO (and indeed removed from the
Random module).

A much nicer way to do the above is using some random monad, for example
from the MonadRandom package. The suggestions from Felipe and Eugene
will work just as well using Rand monad as the IO monad.

Duncan



Hi Duncan,
Can you point me to a tutorial that covers the basics of randomness in 
Hasell? I find it very confusing.


Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Doing people's homework?

2009-09-29 Thread Michael Mossey



Iain Barnett wrote:


So, if I was trying to come up with a solution to a problem that 
possibly has multiple solutions, like building an engine for a car, I 
would do better if I hadn't seen a (well crafted) working engine by 
someone else than if I had?


If effort is there, then give me the example any time, because insight 
will be quicker. If you're going to be lazy then it doesn't matter 
either way.


This could be a question of learning styles. You wrote If the effort is 
there... so I assume that means you have a way of putting effort into 
understanding an engine design, even if you have never seen an engine 
design before. Furthermore you have some way of digesting and transforming 
that knowledge so you can make new designs rather than be a slave to imitation.


I definitely cannot do this very well. I learn much faster by struggling 
with a problem so I learn where the problem is---what is the key thing 
I'm trying to do, and why do my efforts seem to fall short? Why do I feel 
confused? And THEN looking at the answer to get that aha! moment.


This is especially nice in learning Haskell because solutions tend to be 
elegant and contain deep insights.


Isn't there some saying like: See and remember for a day. Do and remember 
for a lifetime.


In struggling to answer, a student is not simpling doing the problem, but 
is actually doing part of the thinking that led to the creation of 
Haskell. They are retracing problems and alternative solutions that are in 
some way related to the history of computer science.


Mike



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: combinatorial search with running bound

2009-09-28 Thread Michael Mossey

Hi Chung-chieh,

When you ask for a pair of boxes, How closely can they be brought together 
without intersection? that provides a lower bound on the question How 
closely can the groups be brought together? (I.e. for that pair of boxes, 
bring them any closer and they intersect, so it is a lower bound.) The 
maximum of all these lower bounds in the minimum needed separation.


-Mike

Chung-chieh Shan wrote:

Michael Mossey m...@alumni.caltech.edu wrote in article 
3942.75.50.175.130.1253997756.squir...@mail.alumni.caltech.edu in 
gmane.comp.lang.haskell.cafe:

The problem is to determine how closely the groups can be brought together
without any boxes intersection.

The basic algorithm is to consider each pair of boxes and ask if they
have any vertical overlap---if so, figure out how closely they can be
brought together without intersecting, otherwise ignore them. Then take
the maximum of those numbers.


Wouldn't you mean minimum instead of maximum then?

I suspect that your code would be clearer without using a state monad.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] combinatorial search with running bound

2009-09-26 Thread Michael Mossey


I have a combinatorial search problem that requires a
running lower bound to be tracked in order to prune the search. I have enough
Haskell experience to know how to do a combinatorial search, for example with
list compresions or the list monad, but I don't know how to keep a running
lower bound.

The problem is: I have two groups of boxes, and need to figure out how
closely the centers of the groups can be brought left-right.

For example,

 55
 1   55
 1
   44
  22   44
  22  +  - how close? - +
   3 
   3 
   3

The left group consists of boxes 1, 2, and 3, which have both a size and
a position (the position is relative to the center of the group,
represented with the +). The right group has boxes 4, 5, and 6.

The problem is to determine how closely the groups can be brought together
without any boxes intersection.

The basic algorithm is to consider each pair of boxes and ask if they
have any vertical overlap---if so, figure out how closely they can be
brought together without intersecting, otherwise ignore them. Then take
the maximum of those numbers.



-- (Here assume lrSeparation returns minBound for boxes that don't have
--  vertical intersection.)
boxesSep :: [Box] - [Box] - Int
boxesSep lefts rights =
maximum [ lrSeparation l r | l - lefts, r - rights ]


However, this algorithm can be improved by pruning.

- Define the 'left extent' of a box by how far its left edge sticks out to
  the left of the group center. Similarly the 'right extent'.

- Sort the list of left boxes in the order of decreasing right extent.
  Sort the list of right boxes in order of decreasing left extent.

- Consider pairs of boxes as a kind of outer loop on the left boxes, and
  inner loop on the right boxes.

- Track the current maximum required separation, which is a lower bound
  on the final answer.

- If at any point in the inner loop, the right extent has gotten so small
  that there's no way you could find a new maximum, skip the rest of the
  inner loop (skip the remainder of the right boxes).

Here's my attempt to write this using a state monad. There's probably a more
idiomatic way to do it.



-- This is state used in the state monad.
data SearchState = SearchState { -- running maximum:
 ssMaximum :: Int
 -- remember the full list of right boxes
 -- so we can initiate a new outer loop
   , ssRights :: [Box]
   }

boxesSep2 :: [Box] - [Box] - Int
boxesSep2 lefts rights =
let ls = sortBy ((flip compare) `on` rightExtent) lefts
rs = sortBy ((flip compare) `on` leftExtent) rights
in fst $ runState (boxesSep2' ls rs) (SearchState minBound rs)

boxesSep2' :: [BoxBounds] - [BoxBounds] - State SearchState Int

-- Termination of algorithm:
boxesSep2' [] _ = gets ssMaximum

-- Initiate a new inner loop:
boxesSep2' (l:ls) [] = do
  rights - gets ssRights
  boxesSep' ls rights

-- Common case:
boxesSep2' lss@(l:ls) (r:rs) = do
  -- In this way of writing the code, we distinguish between the
  -- left/right separation which is the sum of the extents, and the
  -- question of whether there is vertical overlap.
  let v = isVerticalOverlap l r
  sep = lrSeparation l r
  ss - get
  let max = ssMaximum ss
  if sep = max
then boxesSep' ls (ssRights ss) --Here we prune (initiate new inner
loop)
else do
  -- Update max is needed:
  when v (put ss { ssMaximum = sep })
  boxesSep' lss rs


So if there is a better way to do this, I'm all ears.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] combinatorial search with running bound

2009-09-26 Thread Michael Mossey
I made some mistakes in editing this code before posting it. I wrote 
BoxBounds in a couple places when I meant Box. Also made calls to boxesSep' 
when I meant boxesSep2'. Hopefully should all be obvious from context.


Michael Mossey wrote:


I have a combinatorial search problem that requires a
running lower bound to be tracked in order to prune the search. I have enough
Haskell experience to know how to do a combinatorial search, for example with
list compresions or the list monad, but I don't know how to keep a running
lower bound.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] code-build-test cycle

2009-09-17 Thread Michael Mossey
I'm working on a GUI application in qtHaskell, and I have a bit of a bind. 
Using ghci, it launches quickly but runs slowly. On the other hand, 
compiling (mainly linking) takes a while---several minutes. The truth is 
that I can compile it much faster if I selectively import the needed 
modules, so figure the actual compilation/link time is more like 15 to 30 
seconds. (This is Windows on a very old laptop.) I'm used to working in 
Python, so I'm used to a nearly instant code-build-test cycle, and GUI 
applications in PyQt run briskly, faster than ghci/qtHaskell.


Now I'm wondering if Hugs is a faster interpreter.

So during development I don't want to give up the quick cycle you get with 
an interpreter, but the application may be much too slow to use in any 
meaningful way without compilation. Any advice welcome. Maybe there is a 
way to speed up the interpretation.


-Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] adding state in GUIs (qtHaskell)

2009-09-10 Thread Michael Mossey



Dan Weston wrote:

One simple solution is to leave the state in Qt.

As of Qt 4.2, in C++ you can use

  bool QObject::setProperty(const char * name, const QVariant  value)
  QVariant QObject::property(const char * name) const

to set and get properties on any QObject (hence any QWidget).

Since I believe these are (not yet) wrapped in QtHaskell, you can 
instead just create a widget that contains the state and just don't add 
it to a layout. Parent it to a widget and it will quietly disappear when 
its parent dies. If you want it to persist until you say so, don't 
parent it to anything (but then you might as well use Haskell for your 
state!)


Dan


Thanks for the reply, Dan. I don't quite follow---you mean create a widget 
in C++? I can't find setProperty/property in qtHaskell. I would like to 
keep everything in Haskell, though.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] adding state in GUIs (qtHaskell)

2009-09-10 Thread Michael Mossey



Duncan Coutts wrote:

On Wed, 2009-09-09 at 18:29 -0700, Michael P Mossey wrote:
I'm trying to learn qtHaskell. I realize few people on this list know anything 
about qtHaskell, but I have a question that probably relates to all GUIs as 
implemented in Haskell. I just need a hint that could help me figure out the 
next step, which I might be able to infer from the qtHaskell API.


Ultimately it's done by some kind of mutable state, either an IORef,
MVar or a thread.

On top of these you can layer nicer stuff like a state monad (with a
'runState' function that saves and restores from an IORef).

A personal favourite of mine is having the GUI event handler post data
over a channel to a thread. That thread reads from the channel and deals
with the events. The state of the GUI app is then held as local
parameters in that thread.

Doing this of course requires that the GUI lib you're using can cope
with normal Haskell (forkIO) threads. This is possible with gtk2hs, I
don't know about the others.


Hi Duncan, thanks for the reply. Can you point me to some code examples 
that do these things?


-Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] GUI library

2009-08-29 Thread Michael Mossey
I want to choose a GUI library for my project. Some background: I'm a 
beginner to functional programming and have been working through Haskell 
books for a few months now. I'm not just learning Haskell for s**ts and 
giggles; my purpose is to write music-composition-related code; in 
particular, I want to write a graphical musical score editor. (Why write my 
own editor, you may ask? Because I want to fully integrate it with 
computer-assisted-composition algorithms that I plan to write, also in 
Haskell.) I decided to use Haskell for its great features as a functional 
programming language.


Regarding a choice of GUI library, I want these factors:

- it needs to provide at a minimum a drawing surface, a place I can draw 
lines and insert characters, in addition to all the standard widgets and 
layout capabilities we have to come to expect from a GUI library.


- This is a Windows application.

- it needs to be non-confusing for an intermediate-beginner Haskeller. 
Hopefully good documentation and examples will exist on the web.


- It might be nice to have advanced graphics capability such as Qt 
provides, things like antialiasied shapes, and a canvas with efficient 
refresh (refereshes only the area that was exposed, and if your canvas 
items are only primitives, it can do refreshes from within C++ (no need to 
touch your Haskell code at all). However I'm wondering if qtHaskell fits my 
criteria well-documented and lots of examples aimed at beginners.


Thanks,
Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GUI library

2009-08-29 Thread Michael Mossey



Hi Jean-Denis,

Thanks for the information. Do you know how WxHaskell fits my needs? For 
example, does it have good docs and examples for a beginner? Does it have 
the ability to draw lines and characters on a surface? Does it have a type 
of canvas which usually refers to an optimized drawing surface?


Thanks,
Mike


Jean-Denis Koeck wrote:

I began writing a commercial app with a GUI using Gtk2hs,
but it looked ugly on Windows. I'm switching to WxHaskell.

2009/8/29 Michael Mossey m...@alumni.caltech.edu 
mailto:m...@alumni.caltech.edu


I want to choose a GUI library for my project. Some background: I'm
a beginner to functional programming and have been working through
Haskell books for a few months now. I'm not just learning Haskell
for s**ts and giggles; my purpose is to write
music-composition-related code; in particular, I want to write a
graphical musical score editor. (Why write my own editor, you may
ask? Because I want to fully integrate it with
computer-assisted-composition algorithms that I plan to write, also
in Haskell.) I decided to use Haskell for its great features as a
functional programming language.

Regarding a choice of GUI library, I want these factors:

- it needs to provide at a minimum a drawing surface, a place I can
draw lines and insert characters, in addition to all the standard
widgets and layout capabilities we have to come to expect from a GUI
library.

- This is a Windows application.

- it needs to be non-confusing for an intermediate-beginner
Haskeller. Hopefully good documentation and examples will exist on
the web.

- It might be nice to have advanced graphics capability such as Qt
provides, things like antialiasied shapes, and a canvas with
efficient refresh (refereshes only the area that was exposed, and if
your canvas items are only primitives, it can do refreshes from
within C++ (no need to touch your Haskell code at all). However I'm
wondering if qtHaskell fits my criteria well-documented and lots
of examples aimed at beginners.

Thanks,
Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org mailto:Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GUI library

2009-08-29 Thread Michael Mossey



Jason Dagit wrote:

I've never used it myself, but if you're going to be drawing a lot
perhaps cairo is right for you?
http://cairographics.org/hscairo/

I suspect you'll have to be self-taught here.  Gtk2Hs and WxHaskell
are probably the most mature gui libs for Haskell.  Yet with either
one you may end up dropping down into GDI/GDI+ or opengl on windows to
get what you want.  GDI/GDI+ is confusing in any language, but good
books/resources do exist.  So perhaps the trick here is to translate
good documentation from other languages/sources into Haskell examples.
 You could do this as a warm up exercise before starting on your music
editor.

Jason


Thanks, Jason. My drawing needs are pretty rudimentary. A music editor 
doesn't need much more than the ability to draw lines and characters. A 
nice addition would be antialiased curves such as Qt offers but that is 
optional. A so-called canvas sometimes offers optimized drawing updates, 
so the editor doesn't have to redraw the entire page if one portion of it 
changes. That is not strictly necessary, and in fact it wouldn't be hard to 
implement a bit of that functionality myself.


-Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] the problem of design by negation

2009-05-22 Thread Michael Mossey



Conal Elliott wrote:

Hi Michael,

I'm going to hazard a guess.  Please let me know how accurate it is.


Conal,

I think you described this situation well. You must know this kind of
person---I'm sure there's more than one in the world!



When asked to justify his design, the lead software architect explains
everything that *wouldn't* work. We couldn't have a unique key for
every entry because blah blah blah. We couldn't use a garbage collector
because blah blah. We couldn't write a sugar layer because then you have
to document it separately blah blah. So the chosen design seems to be
the only thing left after eliminating everything you can't do.


My guess is that your software architect is making flimsy arguments. 
It's usually very difficult to prove that something *wouldn't* work.  In
 my experience, people make blanket statements about what cannot work, 
when the truth is that they just don't know how and don't have the 
imagination or will even to entertain the possibility of ways that they

 can't yet see.


Yes, that's the impression I get from this guy. His personality causes him
to derive absolute rules or blanket statements from experience, instead of
a more gentle kind of wisdom. The more experience he gets, the more he's
full of constraining rules. So I really did mean to say that his design is
the ONLY thing possible after eliminating everything that won't fit with
his rules.



Instead of using logic and evidence, these people bolster their claims
(often mistakenly called arguments) by putting across confident
language (obviously, clearly, without a doubt), body posture,
facial expression, and voice tone.  When someone is on solid ground,
these bravado tactics are unnecessary.


You got it---the guy is great at winning debates because he is very
confident and can so quickly poke holes (what *seem* to be holes) in any
other position. Moreover, his confidence is why he is lead software
architect... managers are impressed by alpha males and tend to be alpha
males themselves.



Some of my favorite quotes on this dynamic:

Doubt is not a pleasant condition, but certainty is absurd. - Voltaire


They are ill discoverers that think there is no land, when they can see
nothing but sea. - Francis Bacon

To be positive: To be mistaken at the top of one's voice. Ambrose 
Bierce


The greatest obstacle to discovering the shape of the earth, the 
continents, and the oceans was not ignorance but the illusion of 
knowledge. - Daniel J. Boorstin


Good quotes. I was trying to get across this idea of imagination,
creativity, finding solutions in unlikely places.

Here's another one:

The whole trouble with the world is that fools and fanatics are always so
certain of themselves, and wiser people, always so full of doubts.
- Bertrand Russell



advice One thing you may try is to ask the architect for evidence
and/or logical proof of his claims that something cannot work.  As much
as you can, ask from a place of curiosity and even awe.  After all,
existence can often be proved by demonstrating an example, while
non-existence proofs tend to be much more profound.  And stick to your
open-minded disbelief until you really see evidence or logical rigor.
If the architect gets flustered and embarrassed, he may well go on the
attack. After all, bravado signals weak ego, which can quickly become a
cornered animal.  So pay attention to his stress level, and help his
salvage his ego, by suggesting he let you know more about the evidence
and/or logic when he's worked it out.  Be careful to stay in your
integrity, neither going along with someone's forcefulness, nor
representing yourself as having more grounds for confidence than you
really do. /advice


That's good advice. I'm not sure how well this situation can work because
I'm one of these people who is full of doubts, which I regard as
ultimately a positive trait, but it makes me poor at debate. (I know you
are not suggesting I debate him, but he wants to turn everything into a
debate, and it takes a very level-headed outgoing person to keep up with him.)

The best result from this experience is that I can improve my *own* design 
process. For example, I'm working on a personal project related to music, 
and after a few weeks of design, I realized that my thinking had turned 
into design by negation. I felt unhappy with every choice, and started to 
think of the design as the unhappy, but least unhappy, compromise. This is 
probably an old habit of mine. So I want to shift my thinking, by listing 
goals for the design, and finding ways to meet all of them. Win-win instead 
of lose-lose.


Based on a previous reply, I think some people think this sounds like vapid 
cheerleading, but I think you would agree with me that life (and software) 
always offers more possibilities when we engage our imagination with hope 
and energy, not giving up too soon, being willing to sit with problems for 
a time without a definite conclusion.


Thanks,
Mike

[Haskell-cafe] the problem of design by negation

2009-05-20 Thread Michael Mossey
This is not directly related to Haskell, but it's a thought that occurred 
to me after exposure to the Haskell community.


I've spent most of the past 15 years doing scientific programming. The lead 
software architect and software managers are using good software 
engineering practice, though (this is *scientific* programming, not 
*programming by scientists*, ha ha). But, there is a particular culture in 
my company that has become more obvious to me by contrast to the Haskell 
community.


I call it design by negation. When asked to justify his design, the lead 
software architect explains everything that *wouldn't* work. We couldn't 
have a unique key for every entry because blah blah blah. We couldn't use a 
garbage collector because blah blah. We couldn't write a sugar layer 
because then you have to document it separately blah blah. So the chosen 
design seems to be the only thing left after eliminating everything you 
can't do.


I want to aspire to positive design. I want to list the goals, and think 
of design as making clever choices that meet all the goals.


I don't mean to suggest that design is never constrained. It often is. But 
it's a mindset I'm talking about. I don't like this mindset of design by 
negation.


-Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Getting started - help

2009-04-30 Thread Michael Mossey
I'm intermediate-level myself so I hesitate to say something wrong, but I'll go 
ahead and point out the obvious.


applebiz89 wrote:

Hey thanks, that was really helpful actually. I know it must be annoying for
you, and im sorry but ive done what you said, try and compile it to see if
it does and fix it. I have tried every possible way of using brackets in
different place's etc (as u can tell Im not good with haskell at all) but it
still isnt, it must be to do with my data type.

-- Film as datatype

data Film = String String Int [String]


This time you left something off what's called the constructor. (You had it 
there the first time!)


data Film = Film String String Int [String]

Because an algebraic data type can be constructed in potentially more than one 
way, you need a constructor. In this case, you have only one way of constructing 
a Film, so you just name the constructor Film also.




-- List of films

testDatabase :: [Film]
testDatabase = [Casino Royale, Martin Campbell ,2006, [Garry, Dave,
Zoe] ]



And here your problem is that (1) you need to prefix the constructor when making 
a Film, and (2) don't use commas between arguments to the constructor. (In 
Haskell commas are for lists and tuples, and not for function arguments.) So 
this would be how to make one Film:


aFilm :: Film
aFilm = Film Casino Royale Martin Campbell 2006 [Garry, Dave, Zoe]

or

testDatabase = [ Film Casino Royale Martin Campbell 2006 [Garry, Dave, 
Zoe] ]





I get this error:

*** Expression : [Casino Royale,Martin
Campbell,2006,[(Garry,Dave,Zoe)]]
*** Term   : [(Garry,Dave,Zoe)]
*** Type   : [([Char],[Char],[Char])]
*** Does not match : [Char]

Thanks alot!

applebiz

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Is 78 characters still a good option? Was: [Haskell-cafe] breaking too long lines

2009-04-21 Thread Michael Mossey



Robert Greayer wrote:


But the discussion is about a coding standard -- surely if I claimed to like to
have 4 windows side by side, that wouldn't be a good reason to reduce the 
standard
to 40 columns?  Being able to read one line 'at a glance' seems to me to be
improved if that line contains the complete equation, rather than just a 
fragment.
Comprehension of a group of related equations can be improved if they all fit on
one screen (vertically).  Some code that I've written is intended to look like
(and function as) rewrite rules  and looks vastly better with pattern and
replacement all on the same line.  All the arguments can cut both ways -- for
those who like coding with windows side by side, what about those who like 
coding
with one window above another? Coding style is very situational, but the 80
character standard came about due to a once-ubiquitous device limitation (which 
no
longer exists).

The *real* purpose of a coding standard, of course, is to give people something 
to
argue over when they could be actually doing something more productive.  So in 
the
end, it's all good, I suppose.


80 characters may be the device limitation from long ago, but there are other reasons 
to keep lines from getting too long, as have been mentioned... the ease of reading 
vertically, the common use of 80-char windows that can be fit side-by-side. As far as 
arguments cutting both ways, I think it's really a Goldilocks question. Some code 
has lines that are clearly too long to be practical (because they will look ugly as 
they wrap on most people's editors), and 40 characters is clearly too short. 
Somewhere in the middle is just right. Now, we may disagree on what just right 
is, but I just want to establish that the various arguments for longer or shorter 
lines can be regarded as forces that tug the coding standard in one direction or the 
other, and I think it's valuable to look for the equilibrium.


I think 80 characters is a decent compromise. 80-character windows seem to be very 
common. At work everyone uses them, and as monitors got wider, they put windows 
side-by-side. Seems like a common practice.


Mike

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec question

2009-04-17 Thread Michael Mossey

Here's what I've got so far.

-- Text is considered everything up to //. However, the problem
-- is that this consumes the //.
parseText = manyTill anyChar (try (string //))

-- Because the // is already consumed, parseKeyword just grabs
-- the available letters.
parseKeyword :: Parser String
parseKeyword = many1 letter




-- Test function.
parseSome = do t1 - parseText
   k1 - parseKeyword
   t2 - parseText
   return (t1,k1,t2)

On some text//keyword more text// this gives

(some text,keyword, more text)

On some text//keyword more text

this gives the error expecting //

I wonder how I can get the manyTill to be happy with eof before finding the //? 
I tried

parseText = manyTill anyChar (try (string //) | eof)

but got a type error.


minh thu wrote:

2009/4/17 Michael P Mossey m...@alumni.caltech.edu:

I want to write a parser that can read a file with this format: the file has
sections which are demarcated by keywords. Keywords always begin with two
forward slashes and consist of letters, digits, and underscore. The text can
be anything, including special characters. For instance:


//keyword some text
and more text //another_keyword and) some { more text
//ya_keyword $$
-- text


I'm not sure how to write a parser that considers anything but a double
slash to be a valid part of the text.


Maybe you can use a combination of 'many', 'noneOf' or 'manyTill' ?

Cheers,
Thu

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec question

2009-04-17 Thread Michael Mossey

My confusion is that text is by definition followed by // or eof.


minh thu wrote:

You can use 'notFollowedBy' (probably with 'many1' and 'try').
Something like (untested):

notFollowedBy (try $ string //)

Thu

2009/4/17 Michael Mossey m...@alumni.caltech.edu:

Here's what I've got so far.

-- Text is considered everything up to //. However, the problem
-- is that this consumes the //.
parseText = manyTill anyChar (try (string //))

-- Because the // is already consumed, parseKeyword just grabs
-- the available letters.
parseKeyword :: Parser String
parseKeyword = many1 letter




-- Test function.
parseSome = do t1 - parseText
  k1 - parseKeyword
  t2 - parseText
  return (t1,k1,t2)

On some text//keyword more text// this gives

(some text,keyword, more text)

On some text//keyword more text

this gives the error expecting //

I wonder how I can get the manyTill to be happy with eof before finding the
//? I tried

parseText = manyTill anyChar (try (string //) | eof)

but got a type error.


minh thu wrote:

2009/4/17 Michael P Mossey m...@alumni.caltech.edu:

I want to write a parser that can read a file with this format: the file
has
sections which are demarcated by keywords. Keywords always begin with two
forward slashes and consist of letters, digits, and underscore. The text
can
be anything, including special characters. For instance:


//keyword some text
and more text //another_keyword and) some { more text
//ya_keyword $$
-- text


I'm not sure how to write a parser that considers anything but a double
slash to be a valid part of the text.

Maybe you can use a combination of 'many', 'noneOf' or 'manyTill' ?

Cheers,
Thu

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec question

2009-04-17 Thread Michael Mossey



Jason Dusek wrote:

2009/04/17 minh thu not...@gmail.com:

2009/04/17 Michael Mossey m...@alumni.caltech.edu:

I wonder how I can get the manyTill to be happy with eof
before finding the //? I tried

parseText = manyTill anyChar (try (string //) | eof)

but got a type error.

You can use 'notFollowedBy' [...]


  You get a type error because `string //` parses to a
  `String` while `eof` parses to a `()`. Instead you might use:

parseText = manyTill anyChar (try (string //  return ()) | eof)

--
Jason Dusek


Ah.. I think I get it... in the function manyTill, the second argument type doesn't 
matter.. doesn't have to match the first argument type.


Here's what I have so far. It works, but it's a bit weird to consume the // as part 
of the text rather than the keyword. That happens because the try( string // ), 
which is part of the end arg to manyTill, consumes the // when it succeeds. But maybe 
it is the most natural way to express the problem.


parseKeyword :: Parser String
parseKeyword = many1 (alphaNum | char '_')

parseText :: Parser String
parseText = manyTill anyChar ((try (string //)  return ())
  | eof)

parsePair :: Parser (String,String)
parsePair = do k - parseKeyword
   t - parseText
   return (k,t)

parseFile :: Parser [(String,String)]
parseFile = do _ - parseText   -- to skip any text at beginning and 'sync up'
   p - many parsePair
   return p
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] google-like do you mean? feature

2009-04-16 Thread Michael Mossey
I'm thinking of writing a parser to load files that my customers have created. I'm a 
software requirements engineer; the data consists of the customers' thoughts in 
response to the latest release of the requirements doc. In fact, the files will 
probably be copies of the requirements doc itself, into which customers have entered 
their notes and made changes. The original requirements doc will have a format that 
can be parsed; probably something simple like lines marked with codes like


//customer={customer name goes here}
//requirement=
{requirement text goes here}

When I parse the documents that come back from the customers, they are likely to 
contain some errors. Field names may be mangled or misspelled. Customer names may be 
entered in unrecognizable variants (e.g. someone named Michael is indicated as 
Mike) and so forth.


I was thinking that it might be useful to have a Google-like do you mean this? 
feature. If the field name is //customer=, then the parser might recognize a huge 
list of variants like //ustomer=, //customor=, etc... that is, recognize them well 
enough to continue parsing and give a decent error message in context.


Any ideas how to go about this?

I don't think I would create a parser language that includes every variant, but 
instead the field names would be tokens that could be passed to another routine. The 
variants could be generated ahead of time. I would limit the number of variants to 
something manageable, like 10,000 for each field name.


Thanks,
Mike

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] google-like do you mean? feature

2009-04-16 Thread Michael Mossey



Robin Green wrote:

On Wed, 15 Apr 2009 23:31:50 -0700
Michael Mossey m...@alumni.caltech.edu wrote:


I was thinking that it might be useful to have a Google-like do you
mean this? feature. If the field name is //customer=, then the
parser might recognize a huge list of variants
like //ustomer=, //customor=, etc...


You could reduce the probability of such errors by providing a standard
template that could be copy-pasted in wherever necessary.


Yes, that will be there. My example is not so good because it seems concerned with 
the keywords only. I'm more concerned about errors in the data they enter... for 
example, names of people and references to document names.


Thanks,
Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell-beginners] Re: making translation from imperative code

2009-04-02 Thread Michael Mossey
Thanks very much for the help... I will look at this over the next couple of 
days. Your code actually addresses a different problem, the one of merging 
separates lists of timed events. I do need to write code to do that eventually, 
so I will try to understand what you have written here. However, the original 
problem concerns visual layout, which actually takes place *after* creating a 
merged list. In layout, items do have times associated with them, but also take 
up physical space. Different items takes up different amounts of space, and at 
any given time, there may be items on all the staves or  just some of them. I 
will try to come up with


(1) a more succinct explanation of the problem (with textual graphics as a 
visual aid)


(2) a more succinct algorithm.

For example, you are right that I'm mixing concerns. The system layout can 
terminate for two reasons: (1) reached the end of the score (2) reached the 
right edge of the page. There might be a way to simplify the loop or fold so 
that these concerns look more unified.


-Mike

PS a question below:

Heinrich Apfelmus wrote:

Michael Mossey wrote:

Heinrich Apfelmus wrote:

Can you elaborate on what exactly the algorithm is doing? Does it just
emit notes/chords/symbols at given positions or does it also try to
arrange them nicely? And most importantly, where does it emit them to,
i.e. what's the resulting data structure?

So far, the problem looks like a basic fold to me.

Here is some Haskell code that explains the problem in
more detail.
[...]


Thanks for the elaboration.

I think the code doesn't separate concerns very well; mixing information
about widths and times, page size and the recursion itself into one big
gnarl.

Also, there is one important issue, namely returning a special value
like -1 as error code in


 tryAgain state =
   case scoreNextTime score (time state) of
-1 - indicateNoMoreChunks state
 t - layoutSystem' (setTime state t)


Don't do this, use  Maybe  instead

tryAgain state = case scoreNextTime score (time state) of
Nothing - indicateNoMoreChunks state
Just t  - layoutSystem' (state { time = t })

where  Nothing  indicates failure and  Just  success.


Back to the gnarl in general, I still don't have a good grasp on the
problem domain, which is key to structuring the algorithm. Therefore,
I'll expand on toy model and you tell me how it differs from the real thing.

The model is this: we are given several lists of notes (f.i. a piano
part and a vocal line) where each note is annotated with the time it is
to be played at. We abstract away the fact that we are dealing with
musical notes and simply consider a list of *events*

type Time = Integer
type Events a = [(Time, a)]

with the invariant that the timestamps are (strictly) increasing:

valid :: Events a - Bool
valid xs = all $ zipWith (\(t1,_) (t2,_) - t1  t2) xs (drop 1 xs)

Now, the toy task is to merge several lists of similar events into one
big list that is ordered by time as well.

merge :: [Events a] - Events [a]

Since some events may now occur simultaneously, the events of the
results are actually lists of primitive events.

One possibility for implementing  merge  is to start with a function to
merge two event lists

merge2 :: Events [a] - Events [a] - Events [a]
merge2 [] ys = ys
merge2 xs [] = xs
merge2 xs@((tx,x):xt) ys@((ty,y):yt) = case compare tx ty of
  LT - (tx,x   ) : merge2 xt ys
  EQ - (tx,x++y) : merge2 xt yt
  GT - (ty,   y) : merge2 xs yt

and to apply it several times

merge = foldr merge2 [] . map lift
where lift = map $ \(t,x) - (t,[x])


Another possibility is to simply concatenate everything first and then
sort by time

merge = map (\((t,x):xs) - (t,x:map snd xs))
  . groupBy ((==) `on` fst)
  . sortBy (comparing fst)
  . concat


The code above can be made more readable by choosing nice names like

   time  = fst
   event = snd

or avoiding pairs altogether and implementing these names as record
fields. Also, the () combinator from  Control.Arrow  is very handy.

   merge = map (time . head  map event)
 . groupBy ((==) `on` time)
 . sortBy  (comparing time)
 . concat


I hope this gives you a few ideas to think about. How does this toy
model differ from the real thing?


Regards,
apfelmus


PS: If some parts of my example code give you trouble, it's probably
fastest to ask around on the #haskell IRC channel.

--
http://apfelmus.nfshost.com

___
Beginners mailing list
beginn...@haskell.org
http://www.haskell.org/mailman/listinfo/beginners

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] putting SOE 'on the library path'

2009-03-28 Thread Michael Mossey
This is a beginners question, which I have posted to 
beginn...@haskell.org several times, but because I have gotten no 
answer, I thought I would try the cafe.


I'm working through the School of Expression book, and I would like to 
 install the code that comes with the book somewhere. Right now I have 
to write my exercise programs in the same directory where the SOE code 
is sitting so that my exercise programs can import SOE modules.


My platform is Windows.

I tried using the -i options to ghc and ghci, but to no avail. It wasn't 
clear on Windows in what form -i takes its arguments: backslashes as 
usual for Windows, forward slashes perhaps? How about paths with spaces 
in them? Does it need quotes around the filename? I tried all 
combinations. ghc never gave an error indicating there was something 
wrong with what I typed. It happily accepted all forms of -i. But it 
never found the libraries.


Thanks,
Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] putting SOE 'on the library path'

2009-03-28 Thread Michael Mossey
I tried the -v, but I seem to have fixed my problem. It's working now. I 
don't know what I changed. Maybe I typed the paths wrong before. Anyway, 
it does seem to accept (on Windows) paths with backslashes and it 
accepts spaces in the path if you put quotes around it.


I'm still interested, though, in how one installs packages or modules 
so they don't need to be on the path specified by -i. I notice there is 
a file called 'package.conf', which seems related to this.


Martijn van Steenbergen wrote:

Michael Mossey wrote:
I tried using the -i options to ghc and ghci, but to no avail. It 
wasn't clear on Windows in what form -i takes its arguments: 
backslashes as usual for Windows, forward slashes perhaps? How about 
paths with spaces in them? Does it need quotes around the filename? I 
tried all combinations. ghc never gave an error indicating there was 
something wrong with what I typed. It happily accepted all forms of 
-i. But it never found the libraries.


Have you tried starting GHC with -v to see what paths it looks in?

Martijn.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe