Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-11 Thread oleg

I'd like to emphasize that there is a precedent to non-recursive let
in the world of (relatively pure) lazy functional programming.
The programming language Clean has such non-recursive let and uses
it and the shadowing extensively. They consider shadowing a virtue,
for uniquely typed data.

Richard A. O'Keefe wrote
  let (x,s) = foo 1 [] in
  let (y,s) = bar x s in
  let (z,s) = baz x y s in ...
 I really wish you wouldn't do that.
 ...
 I find that that when the same name gets reused like
 that I get very confused indeed about which one I am
 looking at right now.
 ...
 If each instance of the variable is labelled with a
 sequence number, I don't get confused because each
 variable has a different name and I can *see* which
 one this is.

 Yes, sequence numbering variable states is a chore for
 the person writing the code, but it's a boon for the
 person reading the code.

Let me point out the latest Report on the programming language Clean
http://clean.cs.ru.nl/download/doc/CleanLangRep.2.2.pdf
specifically PDF pages 38-40 (Sec 3.5.4 Let-Before Expression). Let me
quote the relevant part:

Many of the functions for input and output in the CLEAN I/O library
are state transition functions. Such a state is often passed from one
function to another in a single threaded way (see Chapter 9) to force
a specific order of evaluation. This is certainly the case when the
state is of unique type. The threading parameter has to be renamed to
distinguish its different versions. The following example shows a
typical example: Use of state transition functions. The uniquely typed
state file is passed from one function to another involving a number
of renamings: file, file1, file2)

readchars:: *File - ([Char], *File)
readchars file
| not ok   = ([],file1)
| otherwise = ([char:chars], file2)
where
  (ok,char,file1) = freadc file
  (chars,file2)   = readchars file1

This explicit renaming of threaded parameters not only looks very
ugly, these kind of definitions are sometimes also hard to read as
well (in which order do things happen? which state is passed in which
situation?). We have to admit: an imperative style of programming is
much easier to read when things have to happen in a certain order such
as is the case when doing I/O. That is why we have introduced
let-before expressions.

It seems the designers of Clean have the opposite view on the explicit
renaming (that is, sequential numbering of unique variables).

Let-before expressions have a special scope rule to obtain an
imperative programming look. The variables in the left- hand side of
these definitions do not appear in the scope of the right-hand side of
that definition, but they do appear in the scope of the other
definitions that follow (including the root expression, excluding
local definitions in where blocks.

Notice that a variable defined in a let-before expression cannot be
used in a where expression. The reverse is true however: definitions
in the where expression can be used in the let before expression.  Use
of let before expressions, short notation, re-using names taking use
of the special scope of the let before)

readchars:: *File - ([Char], *File)
readchars file
#(ok,char,file)   = freadc file
|not ok   = ([],file)
#(chars,file) = readchars file
=([char:chars], file)

The code uses the same name 'file' all throughout, shadowing it
appropriately. Clean programmers truly do all IO in this style, see
the examples in
http://clean.cs.ru.nl/download/supported/ObjectIO.1.2/doc/tutorial.pdf

[To be sure I do not advocate using Clean notation '#' for
non-recursive let in Haskell. Clean is well-known for its somewhat
Spartan notation.]

State monad is frequently mentioned as an alternative. But monads are
a poor alternative to uniqueness typing. Granted, if a function has
one unique argument, e.g., World, then it is equivalent to the ST (or
IO) monad. However, a function may have several unique arguments. For
example, Arrays in Clean are uniquely typed so they can be updated
destructively. A function may have several argument arrays. Operations
on one array have to be serialized (which is what uniqueness typing
accomplishes) but the relative order among operations on distinct
arrays may be left unspecified, for the compiler to determine.

Monads, typical of imperative programs, overspecify the order. For
example,
do
  x - readSTRef ref1
  y - readSTRef ref2
  writeSTRef ref2 (x+y)

the write to ref2 must happen after reading ref2, but ref1 could be
read either before or after ref2. (Assuming ref2 and ref1 are distinct
-- the uniqueness typing will make sure of it.)  Alas, in a monad we
cannot leave the order of reading ref1 and ref2 

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

2013-07-11 Thread AntC
 oleg at okmij.org writes:
 ...
 In Haskell I'll have to uniquely number the s's:
 
 let (x,s1)  = foo 1 [] in
 let (y,s2)  = bar x s1 in
 let (z,s3)  = baz x y s2 in ...
 
 and re-number them if I insert a new statement. 
 
 I once wrote about 50-100 lines of code with the fragment like the
 above and the only problem was my messing up the numbering (at one
 place I used s2 where I should've used s3). ...

Oleg, I hope you are not saying that in production code you use names like 
x, y, z, s1, s2, s3, s4, ...

It leads to opaque code. If even you can mess up, what hope for us with 
only nano-Oleg brain capacity?

Next you'll be wanting GOTO and destructive assignment.

Who knows: one day somebody modifying your code might need to insert a 
line. (That 'somebody' might be your future self.)

Just don't do that! Use long_and_meaningful names.

50-100 near-identical lines of code sounds like an opportunity for an 
algorithm.

AntC


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


[Haskell-cafe] Problem with pipes interpretation of Lazy MapM program.

2013-07-11 Thread Lyndon Maydwell
Hi café.

I've come up with a little version of 'uniq' that should take into account
md5 sums of the file changes... In essence, this:


main :: IO ()
main = getContents
   = mapM check . lines -- PROBLEM
   = mapM_ (putStrLn . ( --  ++ )) . strip

check :: String - IO (String, ABCD)
check s = (s,) . md5 . Str $ readFile s

strip :: (Ord a, Eq b) = [(a,b)] - [a]
strip = concat . uncurry (zipWith look) . (id  maps)

look :: (Ord a, Eq b) = (a,b) - M.Map a b - [a]
look (k,v) m | M.lookup k m == Just v = []
 | otherwise  = [k]

maps :: Ord a = [(a,b)] - [M.Map a b]
maps = scanl (flip (uncurry M.insert)) M.empty


Unfortunately mapM isn't lazy, so this doesn't work. I thought this would
be a good opportunity to try out the Pipes library for a simple real-world
task, but I've come up against some issues with using 'zip' and 'scan' like
functions when translating the code.

This is what I've got so far, but I'm not sure how to proceed:


main :: IO ()
main = runProxy $ stdinS - pipe - stdoutD

pipe :: () - ProxyFast () String () String IO ()
pipe = mapMD check
   - mapScan
  -- zip, check, output go here
   - mapD (( --  ++) . show)

mapScan :: () - ProxyFast () (String, ABCD) () (M.Map String ABCD) IO b
mapScan = scanlp (uncurry M.insert) (M.empty)

check :: String - IO (String, ABCD)
check s = (s,) . md5 . Str $ readFile s

-- Utils

scanlp :: (Monad (p () t a b1 m), Monad m, Functor (p () t a b1 m), Proxy
p) =
  (t - b1 - b1) - b1 - () - p () t a b1 m b
scanlp f a b = do
  void $ respond a
  v - request ()
  scanlp f (f v a) b


There doesn't seem to be any easy zipLike functions, and having to write my
own scan function seems odd. Can someone point me in the right direction
for this?


Thanks!

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


Re: [Haskell-cafe] Music / MIDI help

2013-07-11 Thread Heinrich Apfelmus

Mark Lentczner wrote:

I'm a little lost in the bewildering array of music packages for Haskell,
and need some help.

I'm looking to recreate one of my algorithmic music compositions from the
1980s. I can easily code the logic in Haskell.

I'm looking for a the right set of packages and SW so that I can:
a) generate short sequences and play them immediately, preferrably in ghci,
-- but 'runHaskell Foo.hs | barPlayer' would be acceptable
2) generate MIDI files

I'm on OS X.

So far what I've found is: Haskore, the midi package, and the jack package
- and then I'd need some MIDI software synth for the Mac, and Jack based
patcher Or perhaps I want SuperCollider, and the Haskell bindings - but
that seems rather low level for my needs here (I don't really need to patch
together my instruments, and I don't want to have re-write the whole timing
framework from scratch.)

So - What's a quick easy path here?


I'm also on MacOS X and had the same problem.

For immediate sound output, I liked Rohan Drape's [SuperCollider 
bindings][hsc3], though I started to write my [own 
library][tomato-rubato] that abstracts away from the internals and 
presents a simpler interface. Maybe you can find something interesting 
here. It's currently dormant because the feedback loop in GHCi is still 
too long for my taste, though.


I found Henning Thielemann's [midi][] package very useful for reading 
MIDI files, I guess it's equally useful for writing MIDI files.


  [hsc3]: http://hackage.haskell.org/package/hsc3
  [midi]: http://hackage.haskell.org/package/midi
  [tomato-rubato]: https://github.com/HeinrichApfelmus/tomato-rubato


Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


___
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-11 Thread Edward Kmett
On Wed, Jul 10, 2013 at 3:47 AM, o...@okmij.org wrote:


 Jon Fairbairn wrote:
  It just changes forgetting to use different variable names because of
  recursion (which is currently uniform throughout the language) to
  forgetting to use non recursive let instead of let.

 Let me bring to the record the message I just wrote on Haskell-cafe

 http://www.haskell.org/pipermail/haskell-cafe/2013-July/109116.html

 and repeat the example:

 In OCaml, I can (and often do) write

 let (x,s) = foo 1 [] in
 let (y,s) = bar x s in
 let (z,s) = baz x y s in ...

 In Haskell I'll have to uniquely number the s's:

 let (x,s1)  = foo 1 [] in
 let (y,s2)  = bar x s1 in
 let (z,s3)  = baz x y s2 in ...



 and re-number them if I insert a new statement.


blah = case foo 1 [] of
  (x, s) - case bar x s of
 (y, s) - case baz x y s of
   (z, s) - ...

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


Re: [Haskell-cafe] Non-recursive let

2013-07-11 Thread Doug McIlroy
By analogy to ML, which has let and let rec, where the latter
corresponds to Haskell's let, one is led to let nonrec. I
would definitely not like shadow, for it means that new
variable does NOT cast a shadow on its definining expression.

I fear also that let nonrec by any name would introduce another
attractive nuisance, just as insidious as the one it is intended
to correct. For example
x = ...
let nonrec { x = someFunction x
 xsq = x^2} in ...
won't do what was probably intended. In my own code, this idiom
is more likely than the one that sparked the discussion.

Doug

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


[Haskell-cafe] How to use cabal-dev ghci and multiple targets/build-depends from cabal file?

2013-07-11 Thread Kirill Zaborsky
Currently I'm creating a small library and I wanted to create tests for it. 
So I have a library section in cabal file and also a test-suite section.

Everything goes well but when I tried to load file with tests into ghci 
(actually it was a REPL in emacs) I received errors stating that GHCi can 
not find e.g. Test.Framework module.

Is there any way to use multiple build-depends in GHCi?

KInd regards,
Kirill Zaborsky
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to use cabal-dev ghci and multiple targets/build-depends from cabal file?

2013-07-11 Thread Kirill Zaborsky
The onlys solution I see at the moment is to get rid of cabal-dev and 
install dependencies globally (which works quite OK with gentoo-haskell)

Kind regards,
Kirill Zaborsky

четверг, 11 июля 2013 г., 15:55:15 UTC+4 пользователь Kirill Zaborsky 
написал:

 Currently I'm creating a small library and I wanted to create tests for 
 it. So I have a library section in cabal file and also a test-suite section.

 Everything goes well but when I tried to load file with tests into ghci 
 (actually it was a REPL in emacs) I received errors stating that GHCi can 
 not find e.g. Test.Framework module.

 Is there any way to use multiple build-depends in GHCi?

 KInd regards,
 Kirill Zaborsky

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


Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-11 Thread Michael Snoyman
On Thu, Jul 11, 2013 at 3:44 AM, John Lato jwl...@gmail.com wrote:

 Hi Michael,

 I don't think those are particularly niche cases, but I still think this
 is a bad approach to solving the problem.  My reply to Erik explicitly
 covers the worker thread case, and for running arbitrary user code (as in
 your top line) it's even simpler: just fork a new thread for the user code.
  You can use the async package or similar to wrap this, so it doesn't even
 add any LOCs.

 What I think is particularly niche is not being able to afford the cost of
 another fork, but I strongly doubt that's the case for Warp.

 The reason I think this is a bad design is twofold: first maintaining a
 list of exclusions like this (whether it's consolidated in a function or
 part of the exception instance) seems rather error-prone and increases the
 maintenance burden for very little benefit IMHO.

 Besides, it's still not correct.  What if you're running arbitrary user
 code that forks its own threads?  Then that code's main thread could get a
 BlockedIndefinitelyOnMVar exception that really shouldn't escape the user
 code, but with this approach it'll kill your worker thread anyway.  Or even
 malicious/brain-damaged code that does myThreadId = killThread?

 I like Ertugrul's suggestion though.  It wouldn't fix this issue, but it
 would add a lot more flexibility to exceptions.



I've spent some time thinking about this, and I'm beginning to think the
separate thread approach is in fact the right way to solve this. I think
there's really an important distinction to be made that we've all gotten
close to, but not specifically identified: the exception type itself isn't
really what we're interested, it's how that exception was thrown which is
interesting. I've put together an interesting demonstration[1].

The test I've created is that a worker thread is spawned. In the worker
thread, we run an action and wrap it in a tryAll function. Meanwhile, in
the main thread, we try to read a file and, when it fails, throw that
IOException to the worker thread. In this case, we want the worker thread
to halt execution immediately. With the naive try implementation (tryAll1)
this will clearly not happen, since the async exception will be caught as
if the subaction itself threw the exception. The more intelligent tryAll3
does the same thing, since it is viewing the thrown exception as
synchronous based on its type, when in reality it was thrown as an async
exception.[2] The only approach that handles the situation correctly is
John's separate thread approach (tryAll3). The reason is that it is
properly differentiating based on how the exception was thrown.

I'm going to play around with this a bit more; in particular, I want to see
how this works with monad transformer stacks. But I at least feel like I
have a slightly better conceptual grasp on what's going on here. Thanks for
pointing this out John.

Michael

[1] https://gist.github.com/snoyberg/5975592
[2] You could also do the reverse: thrown an async exception synchronously,
and similarly get misleading results.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-11 Thread Felipe Almeida Lessa
On Thu, Jul 11, 2013 at 10:56 AM, Michael Snoyman mich...@snoyman.com wrote:
 The only
 approach that handles the situation correctly is John's separate thread
 approach (tryAll3).

I think you meant tryAll2 here.  Got me confused for some time =).

Cheers,

--
Felipe.

___
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-11 Thread Carter Schonwald
Yup. Nested cases *are* non recursive lets.

(Can't believe I forgot about that )

On Thursday, July 11, 2013, Edward Kmett wrote:

 On Wed, Jul 10, 2013 at 3:47 AM, o...@okmij.org javascript:_e({},
 'cvml', 'o...@okmij.org'); wrote:


 Jon Fairbairn wrote:
  It just changes forgetting to use different variable names because of
  recursion (which is currently uniform throughout the language) to
  forgetting to use non recursive let instead of let.

 Let me bring to the record the message I just wrote on Haskell-cafe

 http://www.haskell.org/pipermail/haskell-cafe/2013-July/109116.html

 and repeat the example:

 In OCaml, I can (and often do) write

 let (x,s) = foo 1 [] in
 let (y,s) = bar x s in
 let (z,s) = baz x y s in ...

 In Haskell I'll have to uniquely number the s's:

 let (x,s1)  = foo 1 [] in
 let (y,s2)  = bar x s1 in
 let (z,s3)  = baz x y s2 in ...



 and re-number them if I insert a new statement.


 blah = case foo 1 [] of
   (x, s) - case bar x s of
  (y, s) - case baz x y s of
(z, s) - ...

 -Edward

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


Re: [Haskell-cafe] Netwire bouncing ball

2013-07-11 Thread Just

On 07/10/2013 11:44 PM, Ertugrul Söylemez wrote:

A very simple way to do this is to use integralLim_ instead of
integral_.  It allows the ball itself to handle the bouncing.  A less
invasive way (i.e. you can add it to your example) is to use the (--)
combinator:

 ball = integral_ 0 . integral_ 40 . (-9.8)

 aboveGround = require (= 0)

 bouncingBall = aboveGround . ball -- bouncingBall

While this gives you a bouncing ball, the ball will not follow real
physics.  Once the ball hits the ground, it will just start over with
its original velocity.  integralLim_ is the correct solution.


Thank you very much, this works as expected and is easy to understand.
However a complete example of a bouncing ball would be super awesome 
since I have trouble to get it work with integralLim_.


My first try was to use object_ from Control.Wire.Prefab.Move but got 
stuck very quickly.


I think this would be a good addition to the quickstart tutorial.





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


Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-11 Thread Michael Snoyman
On Thu, Jul 11, 2013 at 6:07 PM, Felipe Almeida Lessa 
felipe.le...@gmail.com wrote:

 On Thu, Jul 11, 2013 at 10:56 AM, Michael Snoyman mich...@snoyman.com
 wrote:
  The only
  approach that handles the situation correctly is John's separate thread
  approach (tryAll3).

 I think you meant tryAll2 here.  Got me confused for some time =).

 Cheers,

 --
 Felipe.


Doh, yes, I did, thanks for the clarification.

After playing around with this a bit, I was able to get an implementation
of try, catch, and handle which work for any non-async exception, in monad
transformers which are instances of MonadBaseControl (from monad-control).
I'll try to write up my thoughts in something more coherent, likely a blog
post.

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


[Haskell-cafe] Comparing functions

2013-07-11 Thread Vlatko Basic

Hello Cafe,

I have

data CmpFunction a = CF (a - a - Bool)

that contains comparing functions, like ==, ,  ..., and I'm trying to declare 
the Show instance for it like this


instance Show (CmpFunction a) where
  show (CF (==)) = ==-- no good
  show f = case f of-- no good also
   CBF (==) - ==
_ - Other

but compiler complains for both with

This binding for `==' shadows the existing binding
   imported from `Prelude' at src/Main.hs:6:8-11
   (and originally defined in `ghc-prim:GHC.Classes')

Is it possible at all to compare two functions or how to solve this problem, to 
show some string for a specific function?



br,
vlatko


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


Re: [Haskell-cafe] Comparing functions

2013-07-11 Thread Brandon Allbery
On Thu, Jul 11, 2013 at 1:33 PM, Vlatko Basic vlatko.ba...@gmail.comwrote:

 data CmpFunction a = CF (a - a - Bool)

 that contains comparing functions, like ==, ,  ..., and I'm trying to
 declare the Show instance for it like this

 instance Show (CmpFunction a) where
   show (CF (==)) = ==-- no good
   show f = case f of-- no good also
CBF (==) - ==
 _ - Other

 but compiler complains for both with

 This binding for `==' shadows the existing binding
imported from `Prelude' at src/Main.hs:6:8-11
(and originally defined in `ghc-prim:GHC.Classes')


The problem here isn't quite what you think it is; (==) is not a
constructor, therefore it is a *variable*. It's exactly the same problem as

a = 5
-- ...
foo a = 3 -- this does NOT compare with the previous value of a; it's
identical to the next line!
foo x = x

Just as with the above, the normal way to do it would be to use a guard...
but functions don't have an Eq instance, and *can't* have one. How do you
meaningfully compare them? And for a typeclass function like (==), do you
want (==) instantiated for Int to compare equal to (==) instantiated for
Integer? Does a native-compiled function compare equal to an interpreted
function? Remember referential transparency; the concept of comparing
pointers used in some languages is not applicable to Haskell.

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Well-Typed are hiring: Haskell developer

2013-07-11 Thread Duncan Coutts
Fellow Haskellers,

We are looking to hire a Haskell expert to work with us at Well-Typed as
a Haskell developer. This is an exciting opportunity for someone who is
passionate about Haskell and who is keen to improve and promote Haskell
in a professional context.

The role is quite general and could cover any of the projects and
activities that we are involved in as a company. The tasks may involve:

  * working on the Haskell compiler, libraries and tools;
  * Haskell application development;
  * working directly with clients to solve their problems;
  * teaching Haskell, and developing training materials.

At the moment, we are particularly hoping to find someone with an
interest in supporting the development and maintenance of GHC.
Therefore, some knowledge or interest in compiler internals, operating
systems, the foreign function interface (FFI), and/or deployment issues
would be welcome.

Well-Typed has a variety of clients. For some we do proprietary Haskell
development and consulting. For others, much of the work involves
open-source development and cooperating with the rest of the Haskell
community: the commercial, open-source and academic users.

Our ideal candidate has excellent knowledge of Haskell, whether from
industry, academia, or personal interest. Familiarity with other
languages, low-level programming, and good software engineering
practices are also useful. Good organisation and ability to manage your
own time, and reliably meet deadlines, is important. You should also
have good communication skills. Being interested or having experience in
teaching Haskell (or other technical topics) is a bonus. Experience of
consulting, or running a business, is also a bonus. You are likely to
have a bachelor's degree or higher in computer science or a related
field, although this isn't a requirement.

The offer is initially for a one-year full time contract. We are also
happy to receive applications for part-time work. The annual salary is
from GBP 34,800 or pro rata for part-time or flexible work. We also
operate a bonus scheme. We offer flexible hours and work from home.
Living in England is not required. We may be able to offer either
employment or sub-contracting, depending on the jurisdiction in which
you live.

If you are interested, please apply via i...@well-typed.com. Tell us why
you are interested and why you would be a good fit for the job, and
attach your CV. Please also indicate how soon you might be able to
start. We are more than happy to answer informal enquiries. Contact
Duncan Coutts, Ian Lynagh or Andres Löh for further information, either
by email or IRC.

To ensure we can properly consider your application, please get it to us
by July 25th, 2013, though we may be able to consider applications
received later.

-- 
Duncan Coutts, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com/


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


Re: [Haskell-cafe] Comparing functions

2013-07-11 Thread Timon Gehr

On 07/11/2013 07:33 PM, Vlatko Basic wrote:

Hello Cafe,

I have

 data CmpFunction a = CF (a - a - Bool)

that contains comparing functions, like ==, ,  ..., and I'm trying to
declare the Show instance for it like this

 instance Show (CmpFunction a) where
   show (CF (==)) = ==-- no good
   show f = case f of-- no good also
CBF (==) - ==
 _ - Other

but compiler complains for both with

This binding for `==' shadows the existing binding
imported from `Prelude' at src/Main.hs:6:8-11
(and originally defined in `ghc-prim:GHC.Classes')



Yes, (==) is a variable name in a pattern. Hence you are creating a new 
definition for (==) bound to the constructor argument to CF, which hides 
the (==) defined within the Eq type class.



Is it possible at all to compare two functions


Function types are opaque and values do not have an identity.


or how to solve this problem, to show some string for a specific function?


br,
vlatko


You could store the string alongside the function inside the data type 
in some way.



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


Re: [Haskell-cafe] Comparing functions

2013-07-11 Thread Vlatko Basic

  
  



 Original Message 
  Subject: Re: [Haskell-cafe] Comparing functions
  From: Brandon Allbery allber...@gmail.com
  To: Vlatko Bašić vlatko.ba...@gmail.com
  Cc: Haskell-Cafe haskell-cafe@haskell.org
  Date: 11.07.2013 19:50



  
  On Thu, Jul 11, 2013 at 1:33 PM, Vlatko Basic vlatko.ba...@gmail.com
wrote:

  
    data
  CmpFunction a = CF (a - a - Bool)
  
  that contains comparing functions, like ==, , 
  ..., and I'm trying to declare the Show instance for it
  like this
  
      instance Show (CmpFunction a) where
        show (CF (==)) = "== "                   -- no good
        show f = case f of                            -- no
  good also
                         CBF (==) - "=="
                          _ - "Other"
  
  but compiler complains for both with
  
  This binding for `==' shadows the existing binding
             imported from `Prelude' at src/Main.hs:6:8-11
             (and originally defined in
  `ghc-prim:GHC.Classes')



The problem here isn't quite what you think it
  is; (==) is not a constructor, therefore it is a
  *variable*. It's exactly the same problem as


    a = 5
    -- ...
    foo a = 3 -- this does NOT compare with
  the previous value of "a"; it's identical to the next
  line!
    foo x = x


  

  
  
Hm, I thought it is a pattern match with constant, as in f ('a':xs)
== 



  

  
Just as with the above, the normal way to do
  it would be to use a guard... but functions don't have an
  Eq instance, and *can't* have one. How do you meaningfully
  compare them? And for a typeclass function like (==), do
  you want (==) instantiated for Int to compare equal to
  (==) instantiated for Integer? Does a native-compiled
  function compare equal to an interpreted function?
  Remember referential transparency; the concept of
  comparing pointers used in some languages is not
  applicable to Haskell.


  
  -- 
  
brandon s allbery kf8nh                              
  sine nomine associates
allber...@gmail.com
                                   ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonad        http://sinenomine.net
  

  
  

  


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


Re: [Haskell-cafe] Comparing functions

2013-07-11 Thread Roman Cheplyaka
* Vlatko Basic vlatko.ba...@gmail.com [2013-07-11 19:33:38+0200]
 Hello Cafe,
 
 I have
 
 data CmpFunction a = CF (a - a - Bool)
 
 that contains comparing functions, like ==, ,  ..., and I'm trying
 to declare the Show instance for it like this
 
 instance Show (CmpFunction a) where
   show (CF (==)) = ==-- no good
   show f = case f of-- no good also
CBF (==) - ==
 _ - Other
 
 but compiler complains for both with
 
 This binding for `==' shadows the existing binding
imported from `Prelude' at src/Main.hs:6:8-11
(and originally defined in `ghc-prim:GHC.Classes')
 
 Is it possible at all to compare two functions or how to solve this
 problem, to show some string for a specific function?

Depending on why you need that...

  {-# LANGUAGE FlexibleContexts, UndecidableInstances, FlexibleInstances #-}
  import Test.SmallCheck
  import Test.SmallCheck.Series
  import Test.SmallCheck.Drivers
  import Control.Monad.Identity
  import Data.Maybe

  data CmpFunction a = CF (a - a - Bool)

  feq :: (Show a, Serial Identity a) = CmpFunction a - CmpFunction a - Bool
  feq (CF f1) (CF f2) =
isNothing $
  runIdentity $
smallCheckM 10 (\x1 x2 - f1 x1 x2 == f2 x1 x2)

  instance Show (CmpFunction Integer) where
show f
  | f `feq` CF (==) = ==
  | f `feq` CF (/=) = /=
  | f `feq` CF ()  = 
  | f `feq` CF (=)  = =
  | otherwise = Unknown function

This uses SmallCheck to figure out, with some degree of certainty,
whether two functions are equal.

Of course, Rice's theorem still holds, and the above instance is easy
to fool, but it still might be useful in some cases.

Roman

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


Re: [Haskell-cafe] Comparing functions

2013-07-11 Thread David Thomas
On Thu, Jul 11, 2013 at 10:50 AM, Brandon Allbery allber...@gmail.comwrote:


 ... but functions don't have an Eq instance, and *can't* have one.



Not a general one that's interesting.

There are two Eq instances that'll compile for all functions (not that it's
advisable):

instance Eq ((-) a b) where
 (==) _ _ = True

instance Eq ((-) a b) where
 (==) _ _ = False


You can't get more interesting in the general case, because you can't
inspect the arguments.

If you are okay with distinguishing solely by application you can get a
little more interesting:

instance (Bounded a, Enum a, Eq b) = Eq ((-) a b) where
f == g = all (\ x - f x == g x) [minBound .. maxBound]

*Main () == ()
True
*Main () == (||)
False


Though I'm still not sure I'd say it's a *good idea*...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Comparing functions

2013-07-11 Thread Brandon Allbery
On Thu, Jul 11, 2013 at 2:11 PM, Vlatko Basic vlatko.ba...@gmail.comwrote:

 The problem here isn't quite what you think it is; (==) is not a
 constructor, therefore it is a *variable*. It's exactly the same problem as

  a = 5
 -- ...
 foo a = 3 -- this does NOT compare with the previous value of a;
 it's identical to the next line!
 foo x = x

Hm, I thought it is a pattern match with constant, as in f ('a':xs) ==


I wonder what you'd make of this definition, then?

(*) `on` f = \x y - f x * f y

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Comparing functions

2013-07-11 Thread Vlatko Basic

  
  



 Original Message 
  Subject: Re: [Haskell-cafe] Comparing functions
  From: Brandon Allbery allber...@gmail.com
  To: Vlatko Bašić vlatko.ba...@gmail.com
  Cc: Haskell-Cafe haskell-cafe@haskell.org
  Date: 11.07.2013 20:45



  
  On Thu, Jul 11, 2013 at 2:11 PM, Vlatko Basic vlatko.ba...@gmail.com
wrote:

  

  

  

  The problem here isn't quite what you think
it is; (==) is not a constructor, therefore it
is a *variable*. It's exactly the same problem
as
  


  

  
  
      a = 5
      -- ...
      foo a = 3 -- this does NOT compare
with the previous value of "a"; it's
identical to the next line!
      foo x = x
  
  

  



Hm, I thought it is a pattern match with constant, as in
f ('a':xs) == 
  



I wonder what you'd make of this definition,
  then?


    (*)
  `on` f =
  \x y - f x * f y
 
  

  
  
According to the enlightenment above, I'd say (*) is a variable that
holds some function/operator that is applied on (f x) and (f y), 
not the multiplication, right?


  

  
-- 

  
  
brandon s allbery kf8nh                              
  sine nomine associates
allber...@gmail.com
                                   ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonad        http://sinenomine.net
  

  
  

  


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


Re: [Haskell-cafe] Comparing functions

2013-07-11 Thread Brandon Allbery
On Thu, Jul 11, 2013 at 2:58 PM, Vlatko Basic vlatko.ba...@gmail.comwrote:

 Hm, I thought it is a pattern match with constant, as in f ('a':xs) ==


  I wonder what you'd make of this definition, then?

  (*) `on` f = \x y - f x * f y


 According to the enlightenment above, I'd say (*) is a variable that holds
 some function/operator that is applied on (f x) and (f y),  not the
 multiplication, right?


Correct. But if it's a variable there, why would you expect it to be a
constant in a different pattern?

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Comparing functions

2013-07-11 Thread Vlatko Basic

  
  



 Original Message 
  Subject: Re: [Haskell-cafe] Comparing functions
  From: Brandon Allbery allber...@gmail.com
  To: Vlatko Bašić vlatko.ba...@gmail.com
  Cc: Haskell-Cafe haskell-cafe@haskell.org
  Date: 11.07.2013 21:03



  
  On Thu, Jul 11, 2013 at 2:58 PM, Vlatko Basic vlatko.ba...@gmail.com
wrote:

  

  

  

  

  

  Hm, I thought it is a pattern match with
  constant, as in f ('a':xs) == 

  
  
  
  I wonder what you'd make of this
definition, then?
  
  
      (*) `on` f = \x y - f x * f y
   

  

  
  
According to the enlightenment above, I'd say (*) is a
variable that holds some function/operator that is
applied on (f x) and (f y),  not the multiplication,
right?



Correct. But if it's a variable there, why
  would you expect it to be a constant in a different
  pattern?
  
  
  

  
  
Well, it is confusing that an operator can be a variable. I must get
a habit to understand the meaning by the site, not by the looks.

Thanks for your answers.


  
-- 
  
brandon s allbery kf8nh                              
  sine nomine associates
allber...@gmail.com
                                   ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonad        http://sinenomine.net
  

  
  

  


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


Re: [Haskell-cafe] Non-recursive let

2013-07-11 Thread Andreas Abel

Note that for non-recursive lets

  let' x1 = e1
   x2 = e2

is sequential and *not* the same as the parallel

  let' (x1, x2) = (e1, e2)

The first is

  (\ x1 - (\x2 - ...) e2) e1

and the second is

  (\ (x1,x2) - ...) (e1, e2)

On 11.07.2013 13:36, Doug McIlroy wrote:

By analogy to ML, which has let and let rec, where the latter
corresponds to Haskell's let, one is led to let nonrec. I
would definitely not like shadow, for it means that new
variable does NOT cast a shadow on its definining expression.

I fear also that let nonrec by any name would introduce another
attractive nuisance, just as insidious as the one it is intended
to correct. For example
 x = ...
 let nonrec { x = someFunction x
  xsq = x^2} in ...
won't do what was probably intended. In my own code, this idiom
is more likely than the one that sparked the discussion.

Doug

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




--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

___
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-11 Thread Andreas Abel

I can do this without extra indentation:

  (|) = flip ($)

  f = 5 | \ x -
  6 | \ y -
  x + y

Non-recursive let is as superfluous as the do-notation.

On 11.07.2013 17:40, Carter Schonwald wrote:

Yup. Nested cases *are* non recursive lets.

(Can't believe I forgot about that )

On Thursday, July 11, 2013, Edward Kmett wrote:

On Wed, Jul 10, 2013 at 3:47 AM, o...@okmij.org javascript:_e({},
'cvml', 'o...@okmij.org'); wrote:


Jon Fairbairn wrote:
  It just changes forgetting to use different variable names
because of
  recursion (which is currently uniform throughout the language) to
  forgetting to use non recursive let instead of let.

Let me bring to the record the message I just wrote on Haskell-cafe
http://www.haskell.org/pipermail/haskell-cafe/2013-July/109116.html

and repeat the example:

In OCaml, I can (and often do) write

 let (x,s) = foo 1 [] in
 let (y,s) = bar x s in
 let (z,s) = baz x y s in ...

In Haskell I'll have to uniquely number the s's:

 let (x,s1)  = foo 1 [] in
 let (y,s2)  = bar x s1 in
 let (z,s3)  = baz x y s2 in ...

and re-number them if I insert a new statement.


blah = case foo 1 [] of
   (x, s) - case bar x s of
  (y, s) - case baz x y s of
(z, s) - ...

-Edward



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




--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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


Re: [Haskell-cafe] Netwire bouncing ball

2013-07-11 Thread Oliver Charles
On 07/11/2013 05:52 PM, Just wrote:
 On 07/10/2013 11:44 PM, Ertugrul Söylemez wrote:
 A very simple way to do this is to use integralLim_ instead of
 integral_.  It allows the ball itself to handle the bouncing.  A less
 invasive way (i.e. you can add it to your example) is to use the (--)
 combinator:

  ball = integral_ 0 . integral_ 40 . (-9.8)

  aboveGround = require (= 0)

  bouncingBall = aboveGround . ball -- bouncingBall

 While this gives you a bouncing ball, the ball will not follow real
 physics.  Once the ball hits the ground, it will just start over with
 its original velocity.  integralLim_ is the correct solution.
 
 Thank you very much, this works as expected and is easy to understand.
 However a complete example of a bouncing ball would be super awesome
 since I have trouble to get it work with integralLim_.
 
 My first try was to use object_ from Control.Wire.Prefab.Move but got
 stuck very quickly.
 
 I think this would be a good addition to the quickstart tutorial.

It would indeed be a fantastic addition - this is almost exactly what I
was trying to do as my example netwire project. For a bit more support,
I was trying to move a point from x=0 to x=10, and then back to x=0 -
and so on. I got as far as getting to x=10, but then had no idea how to
reverse the direction and make the whole thing cycle. I was told to read
about ArrowLoop, but sadly I never got much further.

- ollie



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] There was someone here going to use REPA and a functional way to find eigenvalues :)

2013-07-11 Thread KC
Have you succeeded?

In general, is there a functional way to do matrix manipulations?
Linear algebra?
Linear programming?
Integer Programming?
Numerical Analysis?

Casey

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


[Haskell-cafe] Do combinatorial algorithms have a matroid strucutre XOR non-matroid structure?

2013-07-11 Thread KC
I ask this on this mailing list because there are quite a few
mathematically oriented people here.

Casey

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


Re: [Haskell-cafe] Netwire bouncing ball

2013-07-11 Thread Ertugrul Söylemez
Just hask...@justnothing.org wrote:

 Thank you very much, this works as expected and is easy to understand.
 However a complete example of a bouncing ball would be super awesome
 since I have trouble to get it work with integralLim_.

 My first try was to use object_ from Control.Wire.Prefab.Move but got
 stuck very quickly.

object_ is a generalization of integralLim_.  It pretty much allows you
to encode any moving behavior you want.  In general I recommend going
with the integral* wires as far as possible.


 I think this would be a good addition to the quickstart tutorial.

Thanks for your feedback.  I should write a complete example application
in the next revision.


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.


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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-11 Thread Richard A. O'Keefe

On 11/07/2013, at 6:16 PM, o...@okmij.org wrote:

 
 I'd like to emphasize that there is a precedent to non-recursive let
 in the world of (relatively pure) lazy functional programming.

So what?  You can find precedents for almost anything.
I could even point you to a lazy mostly-functional language
with assignment statements in which an identifier occurrence
may refer to two different variables in the course of execution.

Having a precedent doesn't mean that it's a good thing.

 The programming language Clean has such non-recursive let

I am familiar with Clean and used it quite a bit for several years.
My experience with that Clean idiom is *WHY* I hate this usage and
love monads.
 
 Let me point out the latest Report on the programming language Clean
http://clean.cs.ru.nl/download/doc/CleanLangRep.2.2.pdf

which I already have.  If the Clean developers hadn't decided to
concentrate on Windows, leaving the systems I used to wither,
and if they hadn't made fairly massive changes to the language
that broke all my code, it's _possible_ that I might eventually have
come to regard this style as acceptable.

 It seems the designers of Clean have the opposite view on the explicit
 renaming (that is, sequential numbering of unique variables).

That is so.  If that's what you want, you know where to find it.

Like I said, precedent is not proof of goodness.

 
readchars:: *File - ([Char], *File)
readchars file
#(ok,char,file)   = freadc file
|not ok   = ([],file)
#(chars,file) = readchars file
=([char:chars], file)

This is *PRECISELY* the kind of stuff that I find confusing.
If they would just *NUMBER* the states so that I can tell what
is happening when, I would be so much happier.

 The code uses the same name 'file' all throughout, shadowing it
 appropriately. Clean programmers truly do all IO in this style, see
 the examples in
http://clean.cs.ru.nl/download/supported/ObjectIO.1.2/doc/tutorial.pdf
 
 [To be sure I do not advocate using Clean notation '#' for
 non-recursive let in Haskell. Clean is well-known for its somewhat
 Spartan notation.]

I wouldn't call Clean Spartan.  Clean syntax is elaborate.
It achieves brevity not by avoiding keywords but by using
punctuation marks for them, as in [t] vs [!t] vs [|t]
-- does it leap to the eye that [t] is lazy, [!t] is head
strict, and [|t] is strictness-polymorphic? --
and the very important distinction between
a *function* f x = e and a *macro* f x :== e.
(There's a reason why the higher-order list processing
'functions' are actually 'macros'.  See page 109 of the report.
There's precedent for a LOT of things that I don't want in Haskell.)

 State monad is frequently mentioned as an alternative. But monads are
 a poor alternative to uniqueness typing.

In this particular case, uniqueness typing is an utter red herring.
People are advocating state monads JUST TO HIDE THE WIRING, not to
get the effect of destructive assignment.
I *agree* that uniqueness typing is a fine thing and recommended it
to the Mercury developers, who adopted it.

I don't care whether they are called monads, state combinators,
or weeblefretzers.  What I care about is that that
 - the states are HIDDEN from the human reader and
 - they are AUTOMATICALLY wired up correctly for the author.

Suppose we have

# (x,s) = foo s
# (y,z) = bar x s
# (z,s) = ugh x y s

where my finger slipped on the s key in the second line and
pressed the z key instead.  Precisely BECAUSE the variable name
is the same each time, nobody notices, not the compiler, not you,
not me.  The program just goes wrong.

With numbered variables,

let (x,s1) = foo s0
(y,z2) = bar x s1
(z,s3) = ugh x y s2
in ...

the compiler notices that s2 isn't defined.

With suitable combinators,

foo = \x - bar x = \y - ugh x y ...

nobody can make the mistake in the first place,
because the state variable isn't _there_ to get wrong.
 
 Why Clean is relatively unknown? Well, why is Amiga?

Clean is relatively unknown because
 - they started in the Macintosh world, and when
   they provided a compiler for the Unix world,
   they did not port their modern graphics and
   I/O library to it.  So you could never write
   a program that would run on Macs and other things.
 - they then abandoned the Macintosh world for
   Windows.  The Mac IDE was killed off; there is
   now an IDE for Windows but not MacOS or Linux.
 - other major features remain Windows-only
 - the change from Clean 1.3 to Clean 2 was huge,
   like I mentioned above, none of my code survived
   the change, and there was at that time no
   conversion program
 - the available books about Clean are way out of
   date, several drafts of other books remain
   incomplete.
 - the documentation (like the Report) has always been
   rather amateurish and incomplete.  Certainly
   compared with the Haskell documentation.
 - 

Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-11 Thread John Lato
I agree that how the exception was thrown is more interesting than the
type.  I feel like there should be a way to express the necessary
information via the type system, but I'm not convinced it's easy (or even
possible).

Another issue to be aware of is that exceptions can be thrown from pure
code, so if you don't fully evaluate your return value an exception can be
thrown later, outside the catch block.  In practice this usually means an
NFData constraint, or some other constraint for which you can guarantee
evaluation.

In the past I've been pretty vocal about my opposition to exceptions.  It's
still my opinion that they do not make it easy to reason about exceptional
conditions.  Regardless, as Haskell has them and uses them, I'd like to see
improvements if possible.  So if anyone is exploring the design space, I'd
be willing to participate.


On Fri, Jul 12, 2013 at 12:57 AM, Michael Snoyman mich...@snoyman.comwrote:




 On Thu, Jul 11, 2013 at 6:07 PM, Felipe Almeida Lessa 
 felipe.le...@gmail.com wrote:

 On Thu, Jul 11, 2013 at 10:56 AM, Michael Snoyman mich...@snoyman.com
 wrote:
  The only
  approach that handles the situation correctly is John's separate thread
  approach (tryAll3).

 I think you meant tryAll2 here.  Got me confused for some time =).

 Cheers,

 --
 Felipe.


 Doh, yes, I did, thanks for the clarification.

 After playing around with this a bit, I was able to get an implementation
 of try, catch, and handle which work for any non-async exception, in monad
 transformers which are instances of MonadBaseControl (from monad-control).
 I'll try to write up my thoughts in something more coherent, likely a blog
 post.

 Michael

___
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-11 Thread Edward Kmett
Lens even supplies this as ()

On Thu, Jul 11, 2013 at 5:18 PM, Andreas Abel andreas.a...@ifi.lmu.dewrote:

 I can do this without extra indentation:

   (|) = flip ($)

   f = 5 | \ x -
   6 | \ y -
   x + y

 Non-recursive let is as superfluous as the do-notation.


 On 11.07.2013 17:40, Carter Schonwald wrote:

 Yup. Nested cases *are* non recursive lets.

 (Can't believe I forgot about that )

 On Thursday, July 11, 2013, Edward Kmett wrote:

 On Wed, Jul 10, 2013 at 3:47 AM, o...@okmij.org javascript:_e({},

 'cvml', 'o...@okmij.org'); wrote:


 Jon Fairbairn wrote:
   It just changes forgetting to use different variable names
 because of
   recursion (which is currently uniform throughout the language)
 to
   forgetting to use non recursive let instead of let.

 Let me bring to the record the message I just wrote on
 Haskell-cafe
 http://www.haskell.org/**pipermail/haskell-cafe/2013-**
 July/109116.htmlhttp://www.haskell.org/pipermail/haskell-cafe/2013-July/109116.html

 and repeat the example:

 In OCaml, I can (and often do) write

  let (x,s) = foo 1 [] in
  let (y,s) = bar x s in
  let (z,s) = baz x y s in ...

 In Haskell I'll have to uniquely number the s's:

  let (x,s1)  = foo 1 [] in
  let (y,s2)  = bar x s1 in
  let (z,s3)  = baz x y s2 in ...

 and re-number them if I insert a new statement.


 blah = case foo 1 [] of
(x, s) - case bar x s of
   (y, s) - case baz x y s of
 (z, s) - ...

 -Edward



 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe



 --
 Andreas AbelDu bist der geliebte Mensch.

 Theoretical Computer Science, University of Munich
 Oettingenstr. 67, D-80538 Munich, GERMANY

 andreas.a...@ifi.lmu.de
 http://www2.tcs.ifi.lmu.de/~**abel/ http://www2.tcs.ifi.lmu.de/~abel/

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


[Haskell-cafe] OS X ghci problem

2013-07-11 Thread Brian Lewis
Here's a problem variations of which have been plaguing the Haskell
community for as long as I can remember.

To see it for yourself:
1.) Be running OS X
2.) install GLFW-b-1.0.0 (you may need to cabal update) [1]
3.) ghci -package GLFW-b
4.) import Graphics.UI.GLFW as GLFW
5.) GLFW.init

Security camera footage of the crime in progress:
https://gist.github.com/dagit/5980438/raw/2e92a63135008921040478566e56ac7c0556d116/gistfile1.txt

One of the first things GLFW.init does on OS X is
... = [[NSAutoreleasePool alloc] init];

That causes
-[NSAutoreleasePool init]: unrecognized selector sent to instance ...

which seems to mean that NSAutoreleasePool doesn't understand the init
message/method. But [[NSAutoreleasePool alloc] init] is really basic
stuff.

What is going on?

[1]: http://hackage.haskell.org/package/GLFW-b

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