[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 Tillmann Rendel

Michael Mossey wrote:

incrCursor :: State PlayState ()


Additional question: what is proper terminology here?


Proper terminology for monadic things is somewhat debated.


incrCursor is a monad


This is not true.

incrCursor is a monadic type 


incrCursor is not a type, so this can't be correct. However, incrCursor 
has a monadic type is somewhat reasonable. However, I would avoid it 
because it is quite vague.



incrCursor is a monadic function
incrCursor is a monadic computation


These sound good to me. I would prefer the latter, because incrCursor 
does not take any arguments, so it is debatable whether it is a 
function. From my point of view, monadic functions should mean a 
function of type (a - m b) where m is a monad, i.e. arrows in a Kleisli 
category.


An alternative to monadic computation would be monadic action.

However, since we know which monad it is, I would prefer incrCursor is 
a state transformer or even incrCursor is a PlayState transformer.



State is a monad
State is a type constructor of a monad
State is a monadic type 


None of these seem to be true. However, the following is: (State 
PlayState) is a monad.


If you want to say something about State, maybe State is a parametric 
monad or State is a family of monads is appropriate.


  Tillmann
___
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 Neil Brown

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?  With that set of definitions, typing 
plexpand-key should give you playState_ (it expands to the longest 
unambigious expansion), 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.


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.  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.  One 
additional nice thing is that after a completed word, if you press space 
then expand-key again, it inserts the most common next word after your 
previous completion based on open buffers.  Since in Haskell function 
calls and types are separated by spaces, this allows you to quickly 
complete common phrases from your Haskell code.


Thanks,

Neil.
___
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] use of modules to save typing

2010-07-08 Thread John Lato
 From: Michael Mossey m...@alumni.caltech.edu

 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.

I do this as well, although I would probably import like this:

import qualified PlayState as PS

which then allows for PS.cursor

John
___
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 Job Vranish
For working with record fields inside of state monads I would recommend
trying out one of these packages:
lenses
fclabels
data-accessor
(I think I'm forgetting a couple)

They all have special mechanisms for working with record fields inside state
monads (and have lots of other cool stuff)
I'm partial to lenses (I wrote it :) ), but the others are quite good as
well.

Hmmm I just noticed that hackage is not generating the documentation for
latest version of lenses. I shall have to find out why.
In the meantime, the documentation for the 0.1.2 version is essentially the
same.

- Job


On Thu, Jul 8, 2010 at 4:08 AM, Michael Mossey m...@alumni.caltech.eduwrote:

 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

___
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 Stephen Tetley
Hello all

For manipulating records I use an arity family of so-called Starling
combinators - they seem a pleasant if low-powered solution. To me, the
infix combinator style of Data-Accessor quickly ends up looking like a
particulary angry exchange between Snoopy and Woodstock[1].



 star  :: (a - r - ans) - (r - a) - r - ans
 star2 :: (a - b - r - ans) - (r - a) - (r - b) - r - ans
 star3 :: (a - b - c - r - ans) - (r - a) - (r - b) - (r - c) - r 
 - ans
 star4 :: (a - b - c - d - r - ans)
   - (r - a) - (r - b) - (r - c) - (r - d) - r - ans
 star5 :: (a - b - c - d - e - r - ans)
   - (r - a) - (r - b) - (r - c) - (r - d) - (r - e) - r - ans


 star  f fa x  = f (fa x) x
 star2 f fa fb x   = f (fa x) (fb x) x
 star3 f fa fb fc x= f (fa x) (fb x) (fc x) x
 star3 f fa fb fc fd x = f (fa x) (fb x) (fc x) (fd x) x


An example - tracking the source position in a parser:

 data SrcPos = SrcPos {
  src_line   :: Int,
  src_column :: Int,
  src_tab_size   :: Int
}


 incrCol :: SrcPos - SrcPos
 incrCol = star (\i s - s { src_column=i+1 }) src_column

 incrTab :: SrcPos - SrcPos
 incrTab = star2 (\i t s - s { src_column=i+t }) src_column src_tab_size


 incrLine :: SrcPos - SrcPos
 incrLine = star (\i s - s { src_line =i+1, src_column=1 }) src_line

[1] For those missing the cultural reference, in the UK and USA
cartoon characters usually have swearing censored with sequences of
non-alpha characters, e.g. What the @#*! ?
___
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 Nils

On 08.07.2010 11:15, Michael Mossey wrote:

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)


Thats what lambdas are good for:

incrCursor = modify $ \p@(PlayState c l _ _) - p { cursor = min (c+1) 
(l-1) }


Or...

incrCursor = modify $ \...@playstate { cursor = c, len = l } - p { cursor 
= min (c+1) (l-1) }


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