Re: [Haskell-cafe] createProcess running non-existent programs

2012-08-13 Thread Evan Laforge
On Sun, Aug 12, 2012 at 6:18 PM, Niklas Hambüchen m...@nh2.me wrote:
 I just came across the fact that running

 createProcess (proc asdfasdf [])

 with non-existing command asdfasdf returns perfectly fine handles.
 I would expect an exception.
 You can even hGetContents on stdout: You just get .

 I find this highly counter-intuitive. Is this intended?

Yes, I ran into the same thing a while back.  The problem is that the
subprocess has already been forked off before it runs exec() and finds
out the file doesn't exist.  The reason python reports the right error
is that it sets up a pipe from child to parent to communicate just
this error.  It's more friendly, but on the other hand the
implementation is more complicated.

If you don't want to hack up the whole send-exception-over-the-pipe
thing, the easiest thing to do is to wait for the processes's return
code.  If you don't want to do that, you can at least have the
subproces log, e.g.:

loggedProcess :: Process.CreateProcess - IO (Maybe IO.Handle,
   Maybe IO.Handle, Maybe IO.Handle, Process.ProcessHandle)
loggedProcess create = do
r@(_, _, _, pid) - Process.createProcess create
Concurrent.forkIO $ do
code - Process.waitForProcess pid
case code of
Exit.ExitFailure c - notice $
subprocess  ++ show (binaryOf create) ++  failed: 
++ if c == 127 then binary not found else show c
_ - return ()
return r
where
binaryOf create = case Process.cmdspec create of
Process.RawCommand fn _ - fn
Process.ShellCommand cmd - fst $ break (==' ') cmd


As an aside, I've had the idea to at some point go look at the latest
python's version of the subprocess module and see about porting it to
haskell, or at least make sure the haskell version doesn't suffer from
problems fixed in the python one.  They went through a lot of
iterations trying to get it right (and earlier python versions are
broken in one way or another) and we might as well build on their
work.

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


Re: [Haskell-cafe] createProcess running non-existent programs

2012-08-13 Thread Andrew Cowie
On Sun, 2012-08-12 at 23:18 -0700, Evan Laforge wrote:
 Yes, I ran into the same thing a while back.  The problem is that the
 subprocess has already been forked off before it runs exec() and finds
 out the file doesn't exist.

Given how astonishingly common it is to pass an invalid executable name
and/or path, wouldn't it be worth doing a quick probe to see if the file
exists before createProcess actually forks?

[It's not like the effort the OS is going to do for the stat is going to
be thrown away; whether that call pulls it up off of disk or the one
after the fork that exec will do doesn't matter]

AfC
Sydney



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] createProcess running non-existent programs

2012-08-13 Thread David Feuer
In Unix, at least, check, then act is generally considered unwise:
1. Something can go wrong between checking and acting.
2. You might not be checking the right thing(s).  In this case, the fact
that the file exists is not useful if you don't have permission to execute
it. You may not be able to determine whether you have the appropriate
permissions without fairly deep manipulation of ACLs.
3. Even if the OS has the info at hand, making the system call(s) necessary
to get it is not free. Various non-free things happen every time control
passes between user-space and kernel-space.
On Aug 13, 2012 4:17 AM, Andrew Cowie and...@operationaldynamics.com
wrote:

 On Sun, 2012-08-12 at 23:18 -0700, Evan Laforge wrote:
  Yes, I ran into the same thing a while back.  The problem is that the
  subprocess has already been forked off before it runs exec() and finds
  out the file doesn't exist.

 Given how astonishingly common it is to pass an invalid executable name
 and/or path, wouldn't it be worth doing a quick probe to see if the file
 exists before createProcess actually forks?

 [It's not like the effort the OS is going to do for the stat is going to
 be thrown away; whether that call pulls it up off of disk or the one
 after the fork that exec will do doesn't matter]

 AfC
 Sydney


 ___
 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] createProcess running non-existent programs

2012-08-13 Thread Alexander Kjeldaas
This isn't that hard - a pipe shouldn't be needed anymore.  Just require a
post-2003 glibc.

fexecve is a system call in most BSDs.  It is also implemented in glibc
using a /proc hack.

http://www.kernel.org/doc/man-pages/online/pages/man3/fexecve.3.html

Apparently, there are proposals/RFCs to get a system called execveat into
the linux kernel which makes this work properly without /proc.

http://www.gossamer-threads.com/lists/linux/kernel/1574831

Alexander

On 13 August 2012 11:23, David Feuer david.fe...@gmail.com wrote:

 In Unix, at least, check, then act is generally considered unwise:
 1. Something can go wrong between checking and acting.
 2. You might not be checking the right thing(s).  In this case, the fact
 that the file exists is not useful if you don't have permission to execute
 it. You may not be able to determine whether you have the appropriate
 permissions without fairly deep manipulation of ACLs.
 3. Even if the OS has the info at hand, making the system call(s)
 necessary to get it is not free. Various non-free things happen every time
 control passes between user-space and kernel-space.
 On Aug 13, 2012 4:17 AM, Andrew Cowie and...@operationaldynamics.com
 wrote:

 On Sun, 2012-08-12 at 23:18 -0700, Evan Laforge wrote:
  Yes, I ran into the same thing a while back.  The problem is that the
  subprocess has already been forked off before it runs exec() and finds
  out the file doesn't exist.

 Given how astonishingly common it is to pass an invalid executable name
 and/or path, wouldn't it be worth doing a quick probe to see if the file
 exists before createProcess actually forks?

 [It's not like the effort the OS is going to do for the stat is going to
 be thrown away; whether that call pulls it up off of disk or the one
 after the fork that exec will do doesn't matter]

 AfC
 Sydney


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


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


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


[Haskell-cafe] ANNOUNCE: abacate and chuchu

2012-08-13 Thread Marco Túlio Pimenta Gontijo
Hi.

I'm pleased to announce the first release of Abacate and Chuchu.  Chuchu is
a port of Ruby's Cucumber to Haskell, and Abacate is a parser for the Gherkin
language, used by Cucumber.

According to their web site, Cucumber lets software development teams describe
how software should behave in plain text. The text is written in a
business-readable domain-specific language and serves as documentation,
automated tests and development-aid - all rolled into one format.  For more
information on Cucumber: http://cukes.info/

Example of usage for a stack calculator:

calculator.feature:

Feature: Division
  In order to avoid silly mistakes
  Cashiers must be able to calculate a fraction

  Scenario: Regular numbers
Given that I have entered 3 into the calculator
And that I have entered 2 into the calculator
When I press divide
Then the result should be 1.5 on the screen

calculator.hs:

import Control.Applicative
import Control.Monad.IO.Class
import Control.Monad.Trans.State
import Test.Chuchu
import Test.HUnit

type CalculatorT m = StateT [Double] m

enterNumber :: Monad m = Double - CalculatorT m ()
enterNumber = modify . (:)

getDisplay :: Monad m = CalculatorT m Double
getDisplay
  = do
ns - get
return $ head $ ns ++ [0]

divide :: Monad m = CalculatorT m ()
divide = do
  (n1:n2:ns) - get
  put $ (n2 / n1) : ns

defs :: Chuchu (CalculatorT IO)
defs
  = do
Given
  (that I have entered  * number *  into the calculator)
  enterNumber
When I press divide $ const divide
Then (the result should be  * number *  on the screen)
  $ \n
- do
  d - getDisplay
  liftIO $ d @?= n

main :: IO ()
main = chuchuMain defs (`evalStateT` [])

Both packages are available at Hackage at

http://hackage.haskell.org/package/abacate
http://hackage.haskell.org/package/chuchu

I have written them after the specification from Felipe Almeida Lessa.

Any comments are welcome.


-- 
marcot
http://marcot.eti.br/

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


Re: [Haskell-cafe] createProcess running non-existent programs

2012-08-13 Thread Donn Cave
Quoth Evan Laforge qdun...@gmail.com,
...
 ... or at least make sure the haskell version doesn't suffer from
 problems fixed in the python one.

Exactly.  This morning I'm reading suggested solutions that would
work only some of the time, or on only some platforms, which wouldn't
be satisfactory in the long run.

Though speaking of platforms, I guess one large headache would be
what to do about Microsoft operating systems.  Given the unusual
nature of these functions (I mean, what operating-system-independent
command are you going to invoke, anyway?), maybe it would be OK for
the more elaborate support functions to be POSIX / Windows specific.
At the level where people are redirecting the output FD and not the
error FD, etc.

Donn

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


Re: [Haskell-cafe] createProcess running non-existent programs

2012-08-13 Thread Brandon Allbery
On Mon, Aug 13, 2012 at 7:26 AM, Alexander Kjeldaas 
alexander.kjeld...@gmail.com wrote:

 This isn't that hard - a pipe shouldn't be needed anymore.  Just require a
 post-2003 glibc.


So, we are desupporting the *BSDs and OS X (and Solaris etc.) now?  glibc
is only used on Linux and the Hurd (and debian kfreebsd, if that hasn't
fallen on its face yet).

POSIX has some new spawn-type calls, btw, but I don't know how widely
implemented they are or how buggy they are.

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] createProcess running non-existent programs

2012-08-13 Thread Brandon Allbery
On Mon, Aug 13, 2012 at 10:23 AM, Donn Cave d...@avvanta.com wrote:

 Though speaking of platforms, I guess one large headache would be
 what to do about Microsoft operating systems.  Given the unusual


Microsoft provides APIs that work as is for this, by my understanding; it's
the POSIX fork/exec model that makes life difficult.

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] createProcess running non-existent programs

2012-08-13 Thread Donn Cave
Quoth Brandon Allbery allber...@gmail.com,
 On Mon, Aug 13, 2012 at 10:23 AM, Donn Cave d...@avvanta.com wrote:

 Though speaking of platforms, I guess one large headache would be
 what to do about Microsoft operating systems.  Given the unusual


 Microsoft provides APIs that work as is for this, by my understanding; it's
 the POSIX fork/exec model that makes life difficult.

Or interesting, anyway.  I wasn't thinking of the `exception in child'
problem here, so much as more generally, how much is a fully cross-platform
API worth, in a situation where the eventual application of the API is
inherently unlikely to be of a cross platform nature.  The Python version
goes to some length, but can't fully resolve the inconsistencies.  That's
OK if someone wants to go to the trouble, but if I'm right about inherent
platform dependence, it runs the risk of being more irritating than helpful!

Donn

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


Re: [Haskell-cafe] Possible bug in Criterion or Statistics package

2012-08-13 Thread Ryan Newton
Terrible!  Quite sorry that this seems to be a bug in the monad-par library.

I'm copying some of the other monad-par authors and we hopefully can get to
the bottom of this.  If it's not possible to create a smaller reproducer,
is it possible to share the original test that triggers this problem?  In
the meantime, it's good that you can at least run without parallelism.

Best,
  -Ryan

On Sun, Aug 12, 2012 at 11:20 AM, Aleksey Khudyakov 
alexey.sklad...@gmail.com wrote:

 On 10.08.2012 22:20, Till Berger wrote:

  So I am not sure if this is a bug in Criterion itself, the Statistics
 package or any dependency or if I am doing something obviously wrong. I
 would be grateful if someone could look into this as it is holding me
 back from using Criterion for benchmarking my code.

  I would suspect Statistics.Resampling.**resample. From quick glance
 criterion doesn't use any concurrent stuff. I'll try create smaller test
 case


 It looks like I'm wrong. I obtained event log from crashing program
 and resample completed its work without problems. Crash occured later.
 Next
 suspect is bootstrapBCA itself. It uses monad-par to obtain
 parallelism[1].

 I tried to create smaller test case without any success.



 [1]
 https://github.com/bos/**statistics/blob/master/**Statistics/Resampling/
 **Bootstrap.hs#L84https://github.com/bos/statistics/blob/master/Statistics/Resampling/Bootstrap.hs#L84


 Replacing runPar $ parMap with a simple map on that line seems to
 fix the bug. At least I could not reproduce it anymore on several runs
 with my original test case. So it seems to be a bug in the Par monad
 package as this change shouldn't alter the program's behaviour, should it?

  Looks like this is the case. But reducing test case to reasonable size
 (e.g. removing most of criterion and statistics could be quite difficult


 __**_
 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


Re: [Haskell-cafe] Possible bug in Criterion or Statistics package

2012-08-13 Thread Till Berger

Terrible!  Quite sorry that this seems to be a bug in the monad-par library.

I'm copying some of the other monad-par authors and we hopefully can get to
the bottom of this.  If it's not possible to create a smaller reproducer,
is it possible to share the original test that triggers this problem?  In
the meantime, it's good that you can at least run without parallelism.


I have attached an even simpler test that directly uses the monad-par  
library. The function test simply adds one to a list of numbers  
indefinitely using parMap and displays every intermediate result.  
When running the program on multiple cores the bug occurs every time  
for me.


Thanks for looking into this!

Regards,
Till
import Control.Monad.Par

test :: [Int] - IO [Int]
test xs = do
let list = runPar $ parMap (\x - x + 1) xs
putStrLn $ show list
test list

main = do
test [1]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Possible bug in Criterion or Statistics package

2012-08-13 Thread Aleksey Khudyakov

On 13.08.2012 19:43, Ryan Newton wrote:

Terrible!  Quite sorry that this seems to be a bug in the monad-par library.

I'm copying some of the other monad-par authors and we hopefully can get
to the bottom of this.  If it's not possible to create a smaller
reproducer, is it possible to share the original test that triggers this
problem?  In the meantime, it's good that you can at least run without
parallelism.


Here is slightly simplified original test case. By itself program is 
very small but there is statistics and criterion on top of the monad-par
Failure occurs in the function 
Statistics.Resampling.Bootstrap.bootstrapBCA. However I couldn't trigger 
bug with mock data.




import Criterion.Main

test :: t - ()
test _ = ()

main :: IO ()
main = defaultMain [ bench (show n) $ nf test () | n - [0 .. 5000]]


P.S. I assume I've just got test failure report for the statistics from 
your buildbot. Failures reported are spurious. Also linux box cannot 
handle unicode in the output (wrong locale settings?)



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


Re: [Haskell-cafe] Possible bug in Criterion or Statistics package

2012-08-13 Thread Aleksey Khudyakov

On 13.08.2012 20:26, Till Berger wrote:

Terrible! Quite sorry that this seems to be a bug in the monad-par
library.

I'm copying some of the other monad-par authors and we hopefully can
get to
the bottom of this. If it's not possible to create a smaller reproducer,
is it possible to share the original test that triggers this problem? In
the meantime, it's good that you can at least run without parallelism.


I have attached an even simpler test that directly uses the monad-par
library. The function test simply adds one to a list of numbers
indefinitely using parMap and displays every intermediate result. When
running the program on multiple cores the bug occurs every time for me.

Thanks for looking into this!

I've tried your test case and it indeed fails every time. Usually it 
fails with blocked on MVar indefinitely but sometimes it fails with:



[2]
[3]
test: Impossible state in globalWorkComplete.

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


Re: [Haskell-cafe] Data structure containing elements which are instances of the same type class

2012-08-13 Thread Johan Holmquist
That pattern looks so familiar. :) Existential types seem to fit in to the
type system really well so I never got why it is not part of the standard.
On Aug 12, 2012 10:36 AM, Daniel Trstenjak daniel.trsten...@gmail.com
wrote:


 Hi Oleg,

 On Sat, Aug 11, 2012 at 08:14:47AM -, o...@okmij.org wrote:
  I'd like to point out that the only operation we can do on the first
  argument of MkFoo is to show to it. This is all we can ever do:
  we have no idea of its type but we know we can show it and get a
  String. Why not to apply show to start with (it won't be evaluated
  until required anyway)?

 It's only a test case. The real thing is for a game and will be
 something like:

 class EntityT e where
update  :: e - e

render  :: e - IO ()

handleEvent :: e - Event - e

getBound:: e - Maybe Bound


 data Entity = forall e. (EntityT e) = Entity e

 data Level = Level {
entities = [Entity],
...
}


 Greetings,
 Daniel

 ___
 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] Fixity declaration extension

2012-08-13 Thread Ryan Ingram
When I was implementing a toy functional languages compiler I did away with
precedence declarations by number and instead allowed the programmer to
specify a partial order on declarations; this seems to be a much cleaner
solution and avoids arbitrary precedences between otherwise unrelated
operators defined in different modules.

You could write statements like

-- define + and - to have the same precedence
infixl + -

-- define * to have higher precedence than +
infixl * above +

-- define / to have the same precedence as *
infixr / equal *

-- $ is right-associative
infixr $
-- you can also separate precedence from fixity declaration
precedence $ below +

-- function application has higher precedence than all operators by
default, but you can override that
infixl . above APP

-- == is non-associative
infix ==

Here's some parses with this system:

a + b - c   =   (a+b)-c
f.x.y z == g w  = (((f.x).y) z) == (g w)
a == b == c  = parse error (non-associative operator)
a * b / c = parse error (left-associative/right-associative operators with
same precedence)
a == b $ c = parse error (no ordering known between == and $)
a $ b + c = a $ (b+c)

I think this is a much cleaner way to solve the problem and I hope
something like it makes it into a future version of Haskell.

  -- ryan

On Sun, Aug 12, 2012 at 11:46 AM, Евгений Пермяков permea...@gmail.comwrote:

  fixity declaration has form *infix(l|r)? [Digit]* in haskell. I'm pretty
 sure, that this is not enough for complicated cases. Ideally, fixity
 declarations should have form *infix(l|r)? [Digit](\.(+|-)[Digit])** ,
 with implied infinitely long repeated (.0) tail. This will allow fine
 tuning of operator priorities and much easier priority selection. For
 example, it may be assumed, that bit operations like (..) operator have
 hightest priority and have priorities like 9.0.1 or 9.0.2, anti-lisps like
 ($) have lowest priority like 0.0.1, control operators have base priority
 1.* and logic operations like () have priority of 2.* and it will be
 possibly to add new operators between or above all (for example) control
 operators without moving fixity of other ones.

 Agda2 language supports wide priority range, but still without 'tails' to
 my knowledge. Is there any haskell-influenced language or experimental
 syntactic extension that address the issue?

 ___
 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] Data structure containing elements which are instances of the same type class

2012-08-13 Thread Jay Sulzberger



On Mon, 13 Aug 2012, Johan Holmquist holmi...@gmail.com wrote:


That pattern looks so familiar. :) Existential types seem to fit in to the
type system really well so I never got why it is not part of the standard.
On Aug 12, 2012 10:36 AM, Daniel Trstenjak daniel.trsten...@gmail.com
wrote:


Does Haskell have a word for existential type declaration?  I
have the impression, and this must be wrong, that forall does
double duty, that is, it declares a for all in some sense like
the usual for all of the Lower Predicate Calculus, perhaps the
for all of system F, or something near it.

oo--JS.






Hi Oleg,

On Sat, Aug 11, 2012 at 08:14:47AM -, o...@okmij.org wrote:

I'd like to point out that the only operation we can do on the first
argument of MkFoo is to show to it. This is all we can ever do:
we have no idea of its type but we know we can show it and get a
String. Why not to apply show to start with (it won't be evaluated
until required anyway)?


It's only a test case. The real thing is for a game and will be
something like:

class EntityT e where
   update  :: e - e

   render  :: e - IO ()

   handleEvent :: e - Event - e

   getBound:: e - Maybe Bound


data Entity = forall e. (EntityT e) = Entity e

data Level = Level {
   entities = [Entity],
   ...
   }


Greetings,
Daniel

___
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] Fwd: 'let' keyword optional in do notation?

2012-08-13 Thread Ryan Ingram
 But it would be in line with - bindings in the do notation, so maybe it
wouldn't feel so wrong.

I was about to post this exact example.

do
  x - return 1
  x - return x
  return x

seems to work just fine (the answer is 1).  I'd even be ok with =-in-do
being non-recursive like -

  -- ryan

On Thu, Aug 9, 2012 at 1:35 AM, Tillmann Rendel 
ren...@informatik.uni-marburg.de wrote:

 Hi,


 Martijn Schrage wrote:

 Would expanding each let-less binding to a separate let feel more
 sound to you?

  That was actually my first idea, but then two declarations at the same
 level will not be in the same binding group, so

 do x = y
y = 1

 would not compile. This would create a difference with all the other
 places where bindings may appear.


 But it would be in line with - bindings in the do notation, so maybe it
 wouldn't feel so wrong.

   Tillmann


 __**_
 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


Re: [Haskell-cafe] I use cabal install repa but then WinGHCi says module Data.Array.Rep.Algorithms.Ramdomish not found.

2012-08-13 Thread KC
The install of repa-algorithms fails saying it can't cannot find an llvm.


In any case why can't the install syntax be
cabal install repa.algorithms
then it would be more consistent with the import statement.


On Sun, Aug 12, 2012 at 4:00 PM, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:
 I think you need to install repa-algorithms.

 On 13 August 2012 04:18, KC kc1...@gmail.com wrote:
 --
 --
 Regards,
 KC

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



 --
 Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com
 http://IvanMiljenovic.wordpress.com



-- 
--
Regards,
KC

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


Re: [Haskell-cafe] I use cabal install repa but then WinGHCi says module Data.Array.Rep.Algorithms.Ramdomish not found.

2012-08-13 Thread mukesh tiwari
llvm is backend for repa package. Try to install llvm on you system. I
think this can be helpful (
http://llvm.org/releases/3.0/docs/GettingStarted.html ).

Mukesh Tiwari

On Tue, Aug 14, 2012 at 2:47 AM, KC kc1...@gmail.com wrote:

 The install of repa-algorithms fails saying it can't cannot find an llvm.


 In any case why can't the install syntax be
 cabal install repa.algorithms
 then it would be more consistent with the import statement.


 On Sun, Aug 12, 2012 at 4:00 PM, Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com wrote:
  I think you need to install repa-algorithms.
 
  On 13 August 2012 04:18, KC kc1...@gmail.com wrote:
  --
  --
  Regards,
  KC
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
 
  --
  Ivan Lazar Miljenovic
  ivan.miljeno...@gmail.com
  http://IvanMiljenovic.wordpress.com



 --
 --
 Regards,
 KC

 ___
 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] 3 level hierarchy of Haskell objects

2012-08-13 Thread Jay Sulzberger



On Thu, 9 Aug 2012, wren ng thornton w...@freegeek.org wrote:


On 8/8/12 9:41 PM, Jay Sulzberger wrote:

Haskell's type classes look to me to be a provision for declaring
a signature in the sense of the above article.


Just to clarify this in the context of my previous post, type classes define 
signatures in two significantly different ways.


(1) The first way is as you suggest: the methods of a type class specify a 
signature, and for convenience we give that signature a name (i.e., the type 
class' name). However, this is a signature for the term level of Haskell 
(i.e., a signature in the Term sort not discussed previously; elements of 
Type classify elements of Term, just as elements of Kind classify elements of 
Type).


(2) The second way is that, at the type level, the collection of type class 
names together form a signature. Namely they form the signature comprising 
the majority of the Context sort.


Both senses are important for understanding the role of type classes in 
Haskell, but I believe that some of Patrick Browne's confusion is due to 
trying to conflate these into a single notion. Just as terms and types should 
not be confused, neither should methods and type classes. In both cases, each 
is defined in terms of the other, however they live in separate universes. 
This is true even in languages which allow terms to occur in type expressions 
and allow types to occur in term expressions. Terms denote values and 
computations (even if abstractly); whereas, types denote collections of 
expressions (proper types denote collections of term expressions; kinds 
denote collections of type expressions;...).


--
Live well,
~wren


Thanks, wren!

I am attempting to read the Haskell 2010 standard at

  http://www.haskell.org/onlinereport/haskell2010/

It is very helpful and much less obscure than I feared it would be.

What you say about the levels seems reasonable to me now, and I
begin dimly to see an outline of a translation to non-New Type
Theory stuff, which may help me to enter the World of New Type
Theory.

One difficulty which must impede many who study this stuff is
that just getting off the ground seems to require a large number
of definitions of objects of logically different kinds.  (By
logic I mean real logic, not any particular formalized system.)
We must have expressions, values, type expressions, rules of
transformation at the various levels, the workings of the
type/kind/context inference system, etc., to get started.
Seemingly Basic and Scheme require less, though I certainly
mention expressions and values and types and
objects-in-the-Lisp-world in my Standard Rant on^W^WIntroduction
to Scheme.

oo--JS.

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


Re: [Haskell-cafe] createProcess running non-existent programs

2012-08-13 Thread Richard O'Keefe

On 13/08/2012, at 11:26 PM, Alexander Kjeldaas wrote:

 
 This isn't that hard - a pipe shouldn't be needed anymore.  Just require a 
 post-2003 glibc.
 
 fexecve is a system call in most BSDs.  It is also implemented in glibc using 
 a /proc hack.

fexecve is now in the Single Unix Specification, based on
POSIX as of 2008, I believe.  However,
http://www.gnu.org/software/gnulib/manual/html_node/fexecve.html
says
Portability problems not fixed by Gnulib:
  *  This function is missing on many non-glibc platforms: MacOS X 10.5, 
FreeBSD 6.0,
 NetBSD 5.0, OpenBSD 3.8, Minix 3.1.8, AIX 5.1, HP-UX 11, IRIX 6.5, OSF/1 
5.1,
 Solaris 11 2010-11, Cygwin 1.5.x, mingw, MSVC 9, Interix 3.5, BeOS.

That warning doesn't seem to be fully up to date.  I'm using MacOS X 10.6.8
and fexecve() isn't in the manuals or in unistd.h.


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


Re: [Haskell-cafe] Data structure containing elements which are instances of the same type class

2012-08-13 Thread Ryan Ingram
On Mon, Aug 13, 2012 at 12:30 PM, Jay Sulzberger j...@panix.com wrote:

 Does Haskell have a word for existential type declaration?  I
 have the impression, and this must be wrong, that forall does
 double duty, that is, it declares a for all in some sense like
 the usual for all of the Lower Predicate Calculus, perhaps the
 for all of system F, or something near it.


It's using the forall/exists duality:
exsts a. P(a)  =  forall r. (forall a. P(a) - r) - r

For example:
(exists a. Show a = a) = forall r. (forall a. Show a = a - r) - r

This also works when you look at the type of a constructor:

data Showable = forall a. Show a = MkShowable a
-- MkShowable :: forall a. Show a = a - Showable

caseShowable :: forall r. (forall a. Show a = a - r) - Showable - r
caseShowable k (MkShowable x) = k x

testData :: Showable
testData = MkShowable (1 :: Int)

useData :: Int
useData = case testData of (MkShowable x) - length (show x)

useData2 :: Int
useData2 = caseShowable (length . show) testData

Haskell doesn't currently have first class existentials; you need to wrap
them in an existential type like this.  Using 'case' to pattern match on
the constructor unwraps the existential and makes any packed-up constraints
available to the right-hand-side of the case.

An example of existentials without using constraints directly:

data Stream a = forall s. MkStream s (s - Maybe (a,s))

viewStream :: Stream a - Maybe (a, Stream a)
viewStream (MkStream s k) = case k s of
Nothing - Nothing
Just (a, s') - Just (a, MkStream s' k)

takeStream :: Int - Stream a - [a]
takeStream 0 _ = []
takeStream n s = case viewStream s of
Nothing - []
Just (a, s') - a : takeStream (n-1) s'

fibStream :: Stream Integer
fibStream = Stream (0,1) (\(x,y) - Just (x, (y, x+y)))

Here the 'constraint' made visible by pattern matching on MkStream (in
viewStream) is that the s type stored in the stream matches the s type
taken and returned by the 'get next element' function.  This allows the
construction of another stream with the same function but a new state --
MkStream s' k.

It also allows the stream function in fibStream to be non-recursive which
greatly aids the GHC optimizer in certain situations.

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


[Haskell-cafe] Flipping type constructors

2012-08-13 Thread Tony Morris
I have a data-type that is similar to EitherT, however, I have ordered
the type variables like so:

data EitherT (f :: * - *) (a :: *) (b :: *) = ...

This allows me to declare some desirable instances:

instance Functor f = Bifunctor (EitherT f)
instance Foldable f = Bifoldable (EitherT f)
instance Traversable f = Bitraversable (EitherT f)

However, I am unable to declare a MonadTrans instance:

instance MonadTrans (EitherT a) -- kind error

I looked at Control.Compose.Flip to resolve this, but it does not appear
to be kind-polymorphic.
http://hackage.haskell.org/packages/archive/TypeCompose/0.9.1/doc/html/src/Control-Compose.html#Flip

I was wondering if there are any well-developed techniques to deal with
this? Of course, I could just write my own Flip with the appropriate
kinds and be done with it. Maybe there is a more suitable way?


-- 
Tony Morris
http://tmorris.net/



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


Re: [Haskell-cafe] Fixity declaration extension

2012-08-13 Thread AntC
Ryan Ingram ryani.spam at gmail.com writes:

 
 
 When I was implementing a toy functional languages compiler I did away with 
precedence declarations by number and instead allowed the programmer to 
specify a partial order on declarations; this seems to be a much cleaner 
solution and avoids arbitrary precedences between otherwise unrelated 
operators defined in different modules.


I agree. I don't declare operators very often, and when I do I always struggle 
to remember which way round the precedence numbers go. I usually end up 
hunting for a Prelude operator that works the way I'm aiming for, then copy 
its definition. It would be much easier to declare the fixity of myop to be 
same as someotherop (which would presumably have to be already declared/fixed 
in an imported module).

[It's also slightly counterintuitive that the thing being defined comes last 
in an infix declaration, and that the stand-alone operator isn't in parens.]

infixAs !! .$-- fixing myop (.$) to be fixed as Preludeop (!!)

If you wanted to define precedence relative to some other operator(s), it 
might be clearer to give some model parsings (grabbing some syntax something 
like Ryan's):

infix .$ (x ** y .$ z .$ w) == (x ** ((y .$  z) .$ w))
-- === infixl 9 .$


OTOH, I think Евгений's proposal is getting too exotic. Do we really need such 
fine shades of binding? Will the reader remember how each operator binds 
relative to the others? Surely a case where explicit parens would be better.

(Anything else we can bikeshed about while we're at it?)

AntC



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


Re: [Haskell-cafe] Data structure containing elements which are instances of the same type class

2012-08-13 Thread Jay Sulzberger



On Mon, 13 Aug 2012, Ryan Ingram ryani.s...@gmail.com wrote:


On Mon, Aug 13, 2012 at 12:30 PM, Jay Sulzberger j...@panix.com wrote:


Does Haskell have a word for existential type declaration?  I
have the impression, and this must be wrong, that forall does
double duty, that is, it declares a for all in some sense like
the usual for all of the Lower Predicate Calculus, perhaps the
for all of system F, or something near it.



It's using the forall/exists duality:
   exsts a. P(a)  =  forall r. (forall a. P(a) - r) - r


;)

This is, I think, a good joke.  It has taken me a while, but I
now understand that one of the most attractive things about
Haskell is its sense of humor, which is unfailing.

I will try to think about this, after trying your examples.

I did suspect that, in some sense, constraints in combination
with forall could give the quantifier exists.

Thanks, ryan!

oo--JS.




For example:
   (exists a. Show a = a) = forall r. (forall a. Show a = a - r) - r

This also works when you look at the type of a constructor:

   data Showable = forall a. Show a = MkShowable a
   -- MkShowable :: forall a. Show a = a - Showable

   caseShowable :: forall r. (forall a. Show a = a - r) - Showable - r
   caseShowable k (MkShowable x) = k x

   testData :: Showable
   testData = MkShowable (1 :: Int)

   useData :: Int
   useData = case testData of (MkShowable x) - length (show x)

   useData2 :: Int
   useData2 = caseShowable (length . show) testData

Haskell doesn't currently have first class existentials; you need to wrap
them in an existential type like this.  Using 'case' to pattern match on
the constructor unwraps the existential and makes any packed-up constraints
available to the right-hand-side of the case.

An example of existentials without using constraints directly:

   data Stream a = forall s. MkStream s (s - Maybe (a,s))

   viewStream :: Stream a - Maybe (a, Stream a)
   viewStream (MkStream s k) = case k s of
   Nothing - Nothing
   Just (a, s') - Just (a, MkStream s' k)

   takeStream :: Int - Stream a - [a]
   takeStream 0 _ = []
   takeStream n s = case viewStream s of
   Nothing - []
   Just (a, s') - a : takeStream (n-1) s'

   fibStream :: Stream Integer
   fibStream = Stream (0,1) (\(x,y) - Just (x, (y, x+y)))

Here the 'constraint' made visible by pattern matching on MkStream (in
viewStream) is that the s type stored in the stream matches the s type
taken and returned by the 'get next element' function.  This allows the
construction of another stream with the same function but a new state --
MkStream s' k.

It also allows the stream function in fibStream to be non-recursive which
greatly aids the GHC optimizer in certain situations.

 -- ryan



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


Re: [Haskell-cafe] Data structure containing elements which are instances of the same type class

2012-08-13 Thread Alexander Solla
On Mon, Aug 13, 2012 at 6:25 PM, Jay Sulzberger j...@panix.com wrote:



 On Mon, 13 Aug 2012, Ryan Ingram ryani.s...@gmail.com wrote:

  On Mon, Aug 13, 2012 at 12:30 PM, Jay Sulzberger j...@panix.com wrote:

  Does Haskell have a word for existential type declaration?  I
 have the impression, and this must be wrong, that forall does
 double duty, that is, it declares a for all in some sense like
 the usual for all of the Lower Predicate Calculus, perhaps the
 for all of system F, or something near it.


 It's using the forall/exists duality:
exsts a. P(a)  =  forall r. (forall a. P(a) - r) - r


 ;)

 This is, I think, a good joke.  It has taken me a while, but I
 now understand that one of the most attractive things about
 Haskell is its sense of humor, which is unfailing.

 I will try to think about this, after trying your examples.

 I did suspect that, in some sense, constraints in combination
 with forall could give the quantifier exists.


In a classical logic, the duality is expressed by !E! = A, and !A! = E,
where E and A are backwards/upsidedown and ! represents negation.  In
particular, for a proposition P,

Ex Px = !Ax! Px (not all x's are not P)
and
Ax Px = !Ex! Px (there does not exist an x which is not P)

Negation is relatively tricky to represent in a constructive logic -- hence
the use of functions/implications and bottoms/contradictions.  The type
ConcreteType - b represents the negation of ConcreteType, because it shows
that ConcreteType implies the contradiction.

Put these ideas together, and you will recover the duality as expressed
earlier.





 For example:
(exists a. Show a = a) = forall r. (forall a. Show a = a - r) - r

 This also works when you look at the type of a constructor:

data Showable = forall a. Show a = MkShowable a
-- MkShowable :: forall a. Show a = a - Showable

caseShowable :: forall r. (forall a. Show a = a - r) - Showable - r
caseShowable k (MkShowable x) = k x

testData :: Showable
testData = MkShowable (1 :: Int)

useData :: Int
useData = case testData of (MkShowable x) - length (show x)

useData2 :: Int
useData2 = caseShowable (length . show) testData

 Haskell doesn't currently have first class existentials; you need to wrap
 them in an existential type like this.  Using 'case' to pattern match on
 the constructor unwraps the existential and makes any packed-up
 constraints
 available to the right-hand-side of the case.

 An example of existentials without using constraints directly:

data Stream a = forall s. MkStream s (s - Maybe (a,s))

viewStream :: Stream a - Maybe (a, Stream a)
viewStream (MkStream s k) = case k s of
Nothing - Nothing
Just (a, s') - Just (a, MkStream s' k)

takeStream :: Int - Stream a - [a]
takeStream 0 _ = []
takeStream n s = case viewStream s of
Nothing - []
Just (a, s') - a : takeStream (n-1) s'

fibStream :: Stream Integer
fibStream = Stream (0,1) (\(x,y) - Just (x, (y, x+y)))

 Here the 'constraint' made visible by pattern matching on MkStream (in
 viewStream) is that the s type stored in the stream matches the s type
 taken and returned by the 'get next element' function.  This allows the
 construction of another stream with the same function but a new state --
 MkStream s' k.

 It also allows the stream function in fibStream to be non-recursive which
 greatly aids the GHC optimizer in certain situations.

  -- ryan


 __**_
 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


Re: [Haskell-cafe] Data structure containing elements which are instances of the same type class

2012-08-13 Thread Jay Sulzberger



On Mon, 13 Aug 2012, Alexander Solla alex.so...@gmail.com wrote:


On Mon, Aug 13, 2012 at 6:25 PM, Jay Sulzberger j...@panix.com wrote:




On Mon, 13 Aug 2012, Ryan Ingram ryani.s...@gmail.com wrote:

 On Mon, Aug 13, 2012 at 12:30 PM, Jay Sulzberger j...@panix.com wrote:


 Does Haskell have a word for existential type declaration?  I

have the impression, and this must be wrong, that forall does
double duty, that is, it declares a for all in some sense like
the usual for all of the Lower Predicate Calculus, perhaps the
for all of system F, or something near it.



It's using the forall/exists duality:
   exsts a. P(a)  =  forall r. (forall a. P(a) - r) - r



;)

This is, I think, a good joke.  It has taken me a while, but I
now understand that one of the most attractive things about
Haskell is its sense of humor, which is unfailing.

I will try to think about this, after trying your examples.

I did suspect that, in some sense, constraints in combination
with forall could give the quantifier exists.



In a classical logic, the duality is expressed by !E! = A, and !A! = E,
where E and A are backwards/upsidedown and ! represents negation.  In
particular, for a proposition P,

Ex Px = !Ax! Px (not all x's are not P)
and
Ax Px = !Ex! Px (there does not exist an x which is not P)


Yes.



Negation is relatively tricky to represent in a constructive logic -- hence
the use of functions/implications and bottoms/contradictions.  The type
ConcreteType - b represents the negation of ConcreteType, because it shows
that ConcreteType implies the contradiction.


I am becoming sensitized to this distinction.  I now, I think,
feel the impulse toward constructivism, that is, the
assumption/delusion^Waspiration that all functions from the reals
to the reals are continuous.  One argument that helped me goes:

 The reals between 0 and 1 are functions from the integers to say {0, 1}.

 They are attained as limits of functions f: iota(n) - {0, 1}, as
 n becomes larger and larger and ... , where iota(n) is a set with
 n elements, n a finite integer.

 So, our objects, the reals, are attained as limits.  And the
 process of proceeding toward the limit is natural, functorial
 in the sense of category theory.

 Thus so also our morphisms, that is functions from the reals to
 the reals, must be produced functorially as limits of maps
 between objects f: iota(n) - {0, 1}.



Put these ideas together, and you will recover the duality as expressed
earlier.


Thanks!  I am reading some blog posts and I was impressed by the
buffalo hair here:

  
http://existentialtype.wordpress.com/2012/08/11/extensionality-intensionality-and-brouwers-dictum/

oo--JS.










For example:
   (exists a. Show a = a) = forall r. (forall a. Show a = a - r) - r

This also works when you look at the type of a constructor:

   data Showable = forall a. Show a = MkShowable a
   -- MkShowable :: forall a. Show a = a - Showable

   caseShowable :: forall r. (forall a. Show a = a - r) - Showable - r
   caseShowable k (MkShowable x) = k x

   testData :: Showable
   testData = MkShowable (1 :: Int)

   useData :: Int
   useData = case testData of (MkShowable x) - length (show x)

   useData2 :: Int
   useData2 = caseShowable (length . show) testData

Haskell doesn't currently have first class existentials; you need to wrap
them in an existential type like this.  Using 'case' to pattern match on
the constructor unwraps the existential and makes any packed-up
constraints
available to the right-hand-side of the case.

An example of existentials without using constraints directly:

   data Stream a = forall s. MkStream s (s - Maybe (a,s))

   viewStream :: Stream a - Maybe (a, Stream a)
   viewStream (MkStream s k) = case k s of
   Nothing - Nothing
   Just (a, s') - Just (a, MkStream s' k)

   takeStream :: Int - Stream a - [a]
   takeStream 0 _ = []
   takeStream n s = case viewStream s of
   Nothing - []
   Just (a, s') - a : takeStream (n-1) s'

   fibStream :: Stream Integer
   fibStream = Stream (0,1) (\(x,y) - Just (x, (y, x+y)))

Here the 'constraint' made visible by pattern matching on MkStream (in
viewStream) is that the s type stored in the stream matches the s type
taken and returned by the 'get next element' function.  This allows the
construction of another stream with the same function but a new state --
MkStream s' k.

It also allows the stream function in fibStream to be non-recursive which
greatly aids the GHC optimizer in certain situations.

 -- ryan



__**_
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