Re: [Haskell-cafe] List Monads and non-determinism

2013-07-20 Thread Matt Ford
Hi,

Thanks all for your good help.   I was caught up in sequential thinking about 
monads so much so that I treated the lambda expressions as separate functions 
rather than a nested big one. 

That clears up a lot of nagging doubts. 

Cheers,

Matt. 

On 20 Jul 2013, at 00:18, Rogan Creswick cresw...@gmail.com wrote:

 On Fri, Jul 19, 2013 at 3:58 PM, Matt Ford m...@dancingfrog.co.uk wrote:
 Hi,
 
 Thanks for the help.
 
 I thought = was left associative?  It seems to be in the examples from 
 Learn You A Haskell.
 
 I tried to use the associative law to bracket from the right but it didn't 
 like that either...
 
 [1,2] = (\x - (\n - [3,4])) x  = \m - return (n,m))
 
 I think the issue is that you need to first take into account the lambdas 
 *then* use what you know about the properties of (=).
 
 I found this stackoverflow answer helpful 
 (http://stackoverflow.com/a/11237469)
 
 The rule for lambdas is pretty simple: the body of the lambda extends as far 
 to the right as possible without hitting an unbalanced parenthesis.
 
  So, the first lambda runs to the end of the expression:
 
 [1,2] = (\n - [3,4] = \m - return (n,m))
 
 Now, there is still a lambda nested inside the first lambda: \m - return 
 (n,m)
 
 [1,2] = (\n - [3,4] = (\m - return (n,m)))
 
 You violated the implied grouping that these new parentheses make explicit 
 when you tried to apply the associative law above.
 
 Timon's post continues from this point to show the full deconstruction.
 
 --Rogan
 
 
 Any thoughts?
 
 Matt 
 
 On 19 Jul 2013, at 23:35, Rogan Creswick cresw...@gmail.com wrote:
 
 On Fri, Jul 19, 2013 at 3:23 PM, Matt Ford m...@dancingfrog.co.uk wrote:
 I started by putting brackets in
 
 ([1,2] = \n - [3,4]) = \m - return (n,m)
 
 This immediately fails when evaluated: I expect it's something to do
 with the n value now not being seen by the final return.
 
 You're bracketing from the wrong end, which your intuition about n's 
 visibility hints at.  Try this as your first set of parens:
 
  [1,2] = (\n - [3,4] = \m - return (n,m))
 
 --Rogan
  
 
 It seems to me that the return function is doing something more than
 it's definition (return x = [x]).
 
 If ignore the error introduced by the brackets I have and continue to
 simplify I get.
 
 [3,4,3,4] = \m - return (n,m)
 
 Now this obviously won't work as there is no 'n' value.  So what's
 happening here? Return seems to be doing way more work than lifting the
 result to a list, how does Haskell know to do this?  Why's it not in the
 function definition?  Are lists somehow a special case?
 
 Any pointers appreciated.
 
 Cheers,
 
 --
 Matt
 
 ___
 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] List Monads and non-determinism

2013-07-20 Thread Alberto G. Corona
Matt

It is not return, but the bind the one that does the miracle of
multiplication.
By its definition for the list monad, it applies the second term once for
each element are in the first term.
So return is called many times. At the end, bind concat all the small
lists generated


2013/7/20 Matt Ford m...@dancingfrog.co.uk

 Hi All,

 I thought I'd have a go at destructing

 [1,2] = \n - [3,4] = \m - return (n,m)

 which results in [(1,3)(1,4),(2,3),(2,4)]

 I started by putting brackets in

 ([1,2] = \n - [3,4]) = \m - return (n,m)

 This immediately fails when evaluated: I expect it's something to do
 with the n value now not being seen by the final return.

 It seems to me that the return function is doing something more than
 it's definition (return x = [x]).

 If ignore the error introduced by the brackets I have and continue to
 simplify I get.

 [3,4,3,4] = \m - return (n,m)

 Now this obviously won't work as there is no 'n' value.  So what's
 happening here? Return seems to be doing way more work than lifting the
 result to a list, how does Haskell know to do this?  Why's it not in the
 function definition?  Are lists somehow a special case?

 Any pointers appreciated.

 Cheers,

 --
 Matt

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




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


[Haskell-cafe] Default installation path of haskell platform in windows

2013-07-20 Thread Ivan Perez
Hi café,

I just spent the whole day fighting ghc and cabal to get my program
compiled in windows (and I haven't succeeded yet :) )

realgcc is not very happy about paths with spaces in them (I think
there's an open bug about the way ghc calls realgcc, which manifests
if you use extra-lib-dirs in the cabal file).

I'd like to ask you: Might it be wise to change the setup file of the
Haskell Platform to default to an installation path with no spaces in
it, and to tell users why this is a good idea (possibly during the
installation process)?

Other projects are doing the same, including msys.

Please be aware that I know that this solution is far from ideal.
Ideally, it should just work (with spaces and without them). This is
purely a practical decision, a workaround, aiming at making haskell
more accessible to windows users, and making it easier for us to
develop software that works in all platforms.

Regards

Ivan

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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-20 Thread Evan Laforge
On Tue, Jul 16, 2013 at 5:20 PM, Richard A. O'Keefe o...@cs.otago.ac.nz wrote:
 Brian Marick sent me a couple of his stickers.
 The one I have on my door reads to be less wrong than yesterday.
 The other one I keep free to bring out and wave around:

 An example would be handy about now.

Just by coincidence, I recently wrote this:

midi_to_pitch :: TheoryFormat.Format - Maybe Pitch.Key
- Pitch.NoteNumber - Maybe Theory.Pitch
midi_to_pitch fmt key nn =
either (const Nothing) Just $
TheoryFormat.fmt_to_absolute fmt key pitch
where
-- TODO if I support frac I can use this for twelve too
(semis, _frac) = properFraction (Pitch.nn_to_double nn)
Theory.Pitch oct (Theory.Note pc accs) =
Theory.semis_to_pitch_sharps TheoryFormat.piano_layout
(Theory.nn_to_semis semis)
(oct1, pc1) = adjust_octave (TheoryFormat.fmt_pc_per_octave fmt) 7 oct pc
pitch = Theory.Pitch oct1 (Theory.Note pc1 accs)

kbd_to_pitch :: Theory.PitchClass - Pitch.Octave - Theory.PitchClass
- Theory.Accidentals - Theory.Pitch
kbd_to_pitch pc_per_octave oct pc accidentals =
Theory.Pitch (add_oct + oct1) (Theory.Note pc2 accidentals)
where
(oct1, pc1) = adjust_octave pc_per_octave 10 oct pc
-- If the scale is shorter than the kbd, go up to the next octave on the
-- same row.
(add_oct, pc2) = pc1 `divMod` pc_per_octave

adjust_octave :: Theory.PitchClass - Theory.PitchClass - Pitch.Octave
- Theory.PitchClass - (Pitch.Octave, Theory.PitchClass)
adjust_octave pc_per_octave kbd_per_octave oct pc = (oct2, pc2)
where
rows = ceiling $ fromIntegral pc_per_octave / fromIntegral kbd_per_octave
(oct2, offset) = oct `divMod` rows
pc2 = offset * kbd_per_octave + pc


Also, fragments like this are fairly common:

Right pitch_ -
let pitch = pitch_
{ Theory.pitch_note = (Theory.pitch_note pitch_)
{ Theory.note_accidentals = 0 }
}
accs = Theory.pitch_accidentals pitch_
in Just $ ScaleDegree.scale_degree_just
(smap_named_intervals smap)
(smap_accidental_interval smap ^^ accs)
(pitch_nn smap pitch) (pitch_note fmt pitch)

My convention is when I have a a series of transformations that have
to be named for whatever reason, I suffix with numbers.  When I have a
function argument (or case-bound variable as in this case) that has to
be cooked before it can be used, I suffix it with _.  That way code
inside the function is not likely to accidentally use the un-cooked
version (this has happened when I left the uncooked version normal and
suffixed the cooked version with a 1 or something).  In monadic style,
I use 'x - return $ f x' a fair amount.

I'm just sending this to point out that it actually is a real issue.
And on the odd chance that someone wants to tell me that I'm doing it
wrong and here's a better idea :)  I'm not about to import Monad.State
and wrap the whole expression in a state call just to replace one or
two variables, both the syntactic overhead and the conversion
overhead make it not worth it.

However, I'm also not agitating for a non-recursive let, I think that
ship has sailed.  Besides, if it were added people would start
wondering about non-recursive where, and it would introduce an
exception to haskell's pretty consistently order-independent
declaration style.

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


Re: [Haskell-cafe] Dynamic and equality

2013-07-20 Thread adam vogt
On Sat, Jul 20, 2013 at 12:31 AM, Carter Schonwald
carter.schonw...@gmail.com wrote:
 the tricky part then is to add support for other types.

 another approach to existentially package type classes with the data type!

 eg
 data HasEq  = forall a . HasEq ( Eq a = a)
 or its siblinng
 data HasEq a = Haseq (Eq a = a )

 note this requires more planning in how you structure your program, but is a
 much more pleasant approach than using dynamic when you can get it to suite
 your application needs.

 note its also late, so I've not type checked these examples ;)

Hi Carter,

It doesn't seem like the existential one will work as-is, since ghc
rejects this:

{-# LANGUAGE ExistentialQuantification #-}
data HEQ = forall a. Eq a = HEQ a
usingHEQ :: HEQ - HEQ - Bool
usingHEQ (HEQ a) (HEQ b) = a == b


I think you were hinting at this option which is better than my first
suggestion:

{-# LANGUAGE ExistentialQuantification #-}
import Data.Typeable
data DYN = forall a. Typeable a = DYN (a, DYN - Bool)

mkDyn :: (Eq a, Typeable a) = a - DYN
mkDyn x = DYN (x, \(DYN (y, eq2)) - case cast y of
Just y' - x == y'
_ - False)

mkDyn' :: Typeable a = a - DYN
mkDyn' x = DYN (x, \_ - False)

eqDyn :: DYN - DYN - Bool
eqDyn x@(DYN (_, fx)) y@(DYN (_,fy)) = fx y || fy x


Maybe there's some way to get mkDyn' and mkDyn as the same function,
without having to re-write all of the Eq instances as a 2-parameter
class like http://www.haskell.org/haskellwiki/GHC/AdvancedOverlap.


--
Adam

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


Re: [Haskell-cafe] Wrapping all fields of a data type in e.g. Maybe

2013-07-20 Thread adam vogt
On Sat, Jul 20, 2013 at 12:14 AM, Michael Orlitzky mich...@orlitzky.com wrote:
 For posterity, I report failure =)

Hi Michael,

It's fairly straightforward to generate the new data with template
haskell [1], and on the same page, section 10.7 'generic' zipWith is
likely to be similar to your merging code.

[1] 
http://www.haskell.org/haskellwiki/Template_Haskell#Generating_records_which_are_variations_of_existing_records

--
Adam

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


Re: [Haskell-cafe] List Monads and non-determinism

2013-07-20 Thread Eric Rasmussen
For the sake of approaching this in yet another way, it can also be helpful
to substitute the definitions of bind and return in your expression. If we
start with the definitions:

instance Monad [] where
  xs = f = concat (map f xs)
  return x = [x]

Then we can make the following transformations:

  [1,2] = \n - [3,4] = \m - return (n,m)

  [1,2] = \n - [3,4] = \m - [(n, m)]

  [1,2] = \n - concat (map (\m - [(n, m)]) [3,4])

  concat (map (\n - concat (map (\m - [(n, m)]) [3,4])) [1,2])

Or perhaps more simply:

  concatMap (\n - concatMap (\m - [(n, m)]) [3,4]) [1,2]

All of which are valid expressions and produce the same value.

Depending on your learning style this might not be as helpful as the other
approaches, but it does take a lot of the mystery out of = and return.






On Sat, Jul 20, 2013 at 1:08 AM, Alberto G. Corona agocor...@gmail.comwrote:

 Matt

 It is not return, but the bind the one that does the miracle of
 multiplication.
 By its definition for the list monad, it applies the second term once for
 each element are in the first term.
 So return is called many times. At the end, bind concat all the small
 lists generated


 2013/7/20 Matt Ford m...@dancingfrog.co.uk

 Hi All,

 I thought I'd have a go at destructing

 [1,2] = \n - [3,4] = \m - return (n,m)

 which results in [(1,3)(1,4),(2,3),(2,4)]

 I started by putting brackets in

 ([1,2] = \n - [3,4]) = \m - return (n,m)

 This immediately fails when evaluated: I expect it's something to do
 with the n value now not being seen by the final return.

 It seems to me that the return function is doing something more than
 it's definition (return x = [x]).

 If ignore the error introduced by the brackets I have and continue to
 simplify I get.

 [3,4,3,4] = \m - return (n,m)

 Now this obviously won't work as there is no 'n' value.  So what's
 happening here? Return seems to be doing way more work than lifting the
 result to a list, how does Haskell know to do this?  Why's it not in the
 function definition?  Are lists somehow a special case?

 Any pointers appreciated.

 Cheers,

 --
 Matt

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




 --
 Alberto.

 ___
 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] HaskellWiki images disappeared

2013-07-20 Thread Thomas Schilling
Should be fixed now. The wiki was recently transferred to a new server and
this got unfortunately broken in the process.
On 18 Jul 2013 22:45, Henk-Jan van Tuyl hjgt...@chello.nl wrote:



 L.S.,

 It looks like the HaskellWiki images have disappeared; can anybody repair
 this? (See for example http://www.haskell.org/**haskellwiki/Special:**
 MostLinkedFileshttp://www.haskell.org/haskellwiki/Special:MostLinkedFiles)

 Regards,
 Henk-Jan van Tuyl


 --
 Folding@home
 What if you could share your unused computer power to help find a cure? In
 just 5 minutes you can join the world's biggest networked computer and get
 us closer sooner. Watch the video.
 http://folding.stanford.edu/


 http://Van.Tuyl.eu/
 http://members.chello.nl/**hjgtuyl/tourdemonad.htmlhttp://members.chello.nl/hjgtuyl/tourdemonad.html
 Haskell programming
 --

 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://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] ANN: darcsden 1.1 released, darcs hub news 2013/07

2013-07-20 Thread Simon Michael
Hi all, here is a combined darcsden and darcs hub update.

darcsden 1.1 released
=

darcsden 1.1 is now available on hackage! This is the updated version
of darcsden which runs hub.darcs.net, so these changes are also
relevant to that site's users. (More darcs hub news below.)

darcsden is a web application for browsing and managing darcs
repositories, issues, and users, plus a basic SSH server which lets
users push changes without a system login. It is released under the
BSD license. You can use it:

- to browse and manage your local darcs repos with a more comfortable UI
- to make your repos browsable online, optionally with issue tracking
- to run a multi-user darcs hosting site, like hub.darcs.net

http://hackage.haskell.org/package/darcsden - cabal package \
http://hub.darcs.net/simon/darcsden - source \
http://hub.darcs.net/simon/darcsden/issues  - bug tracker

Release notes for 1.1
-

Fixed:

* 16: Layout of links and navigation places them offscreen
* 21: anchors on line numbers exist but line numbers not clickable
* 28: forking then deleting a private repo makes repos unviewable
* 29: darcs get to an invalid ssh repo url hangs
* 46: if user kills a push, the lock file is not removed, preventing
  subsequent pushes

New:

* the signup page security question is case-insensitive (darcs)
* login redirects to the my repos page
* a more responsive layout, with content first, buttons at top/right
* many other UI updates; font, headings, borders, whitespace, robustness
* more context sensitivity in buttons  links
* better next/previous page controls
* better support for microsoft windows, runs as a service
* builds with GHC 7.6 and latest libraries
* easier developer builds

Brand new, from the Enhancing Darcsden GSOC (some WIP):

* you can sign up, log in, and link existing accounts with your Google
  or Github id
* you can reset your password
* you can edit files through the web
* you can pack your repositories, allowing faster darcs get

Detailed change log: http://hub.darcs.net/simon/darcsden/CHANGES.md

How to help
---

darcsden is a small, clean codebase that is fun to hack on. Discussion
takes place on the #darcs IRC channel, and useful changes will quickly
be deployed at hub.darcs.net, providing a tight dogfooding/feedback
loop. Here's how to contribute a patch there:

1. register at hub.darcs.net
2. add your ssh key in settings so you can push
3. fork your own branch: http://hub.darcs.net/simon/darcsden , fork
4. copy to your machine: darcs get http://hub.darcs.net/yourname/darcsden
5. make changes, darcs record
6. push to hub: darcs push yourn...@hub.darcs.net:darcsden --set-default
7. your change will appear at http://hub.darcs.net/simon/darcsden/patches
8. discuss on #darcs, or ping me (sm, si...@joyful.com) to merge it

Credits
---

Alex Suraci created darcsden. Simon Michael led this release, which
includes contributions from Alp Mestanogullari, Jeffrey Chu, Ganesh
Sittampalam, and BSRK Aditya (sponsored by Google's Summer of Code).
And last time I forgot to mention two 1.0 contributors: Bertram
Felgenhauer and Alex Suraci.

darcsden depends on Darcs, Snap, GHC, and other fine projects from the
Haskell ecosystem, as well as Twitter Bootstrap, JQuery, and many more.





darcs hub news 2013/07
==

http://hub.darcs.net , aka darcs hub, is the darcs repository hosting
site I operate. It's like a mini github, but using darcs. You can:

- browse users, repos, files and changes
- publish darcs repos publicly or privately
- get, push and pull repos over ssh
- grant push access to other members
- fork repos, then view and merge upstream and downstream changes
- track issues

The site was announced on 2012/9/15
(http://thread.gmane.org/gmane.comp.version-control.darcs.user/26556).
Since then:

- The site has been deploying new darcsden work promptly; it includes
  all the 1.1 release improvements described above.

- The server's ram has doubled from 1G to 2G (thanks Linode). This
  means app restarts due to excessive memory use are less frequent.

- The front page's user list had become slow and has been optimised,
  halving the page load time.

- BSRK Aditya is doing his Google Summer of Code project on enhancing
  darcsden and darcs hub (mentored by darcs developer Ganesh
  Sittampalam). Find out more at http://darcs.net/GSoC/2013-Darcsden .

- The site is being used, with many small projects and a few
  well-known larger ones. Quick stats as of 2013/07/19:

user accounts   317
repos   579
disk usage2.5G
uptime last 30 days  99.48%
average response time last 30 days1.6s

- The site remains free to use, including private repos.  Eventually,
  some kind of funding will be needed to keep it self-sustaining, and
  could also enable faster 

[Haskell-cafe] ANN: data-fin

2013-07-20 Thread wren ng thornton

-- data-fin 0.1.0


The data-fin package offers the family of totally ordered finite sets,
implemented as newtypes of Integer, etc. Thus, you get all the joys of:

data Nat = Zero | Succ !Nat

data Fin :: Nat - * where
FZero :: (n::Nat) - Fin (Succ n)
FSucc :: (n::Nat) - Fin n - Fun (Succ n)

But with the efficiency of native types instead of unary encodings.



-- Notes


I wrote this package for a linear algebra system I've been working on, but
it should also be useful for folks working on Agda, Idris, etc, who want
something more efficient to compile down to in Haskell. The package is
still highly experimental, and I welcome any and all feedback.

Note that we implement type-level numbers using [1] and [2], which works
fairly well, but not as nicely as true dependent types since we can't
express certain typeclass entailments. Once the constraint solver for
type-level natural numbers becomes available, we'll switch over to using
that.

[1] Oleg Kiselyov and Chung-chieh Shan. (2007) Lightweight static
resources: Sexy types for embedded and systems programming. Proc. Trends
in Functional Programming. New York, 2--4 April 2007.
http://okmij.org/ftp/Haskell/types.html#binary-arithm

[2] Oleg Kiselyov and Chung-chieh Shan. (2004) Implicit configurations:
or, type classes reflect the values of types. Proc. ACM SIGPLAN 2004
workshop on Haskell. Snowbird, Utah, USA, 22 September 2004. pp.33--44.
http://okmij.org/ftp/Haskell/types.html#Prepose



-- Links


Homepage:
http://code.haskell.org/~wren/

Hackage:
http://hackage.haskell.org/package/data-fin

Darcs:
http://community.haskell.org/~wren/data-fin

Haddock (Darcs version):
http://community.haskell.org/~wren/data-fin/dist/doc/html/data-fin

-- 
Live well,
~wren


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