Re: [Haskell-cafe] Need urgent help with Network.tls

2013-02-23 Thread Jason Dusek
2013/2/23 C K Kashyap ckkash...@gmail.com:
 The reason I want to use TLS is that I'd want to pack the whole thing in a
 DLL and give it off to a friend for use.

Why does this requirement compel you to forego the imapget or HaskellNet
packages?

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: [Haskell-cafe] DIY vs as-a-Service with MemCachier

2013-01-17 Thread Jason Dusek
2013/1/17 Kazu Yamamoto k...@iij.ad.jp:
 The following blog post by Joyent is worth reading:

 http://joyent.com/blog/diy-vs-as-a-service-with-memcachier

 We don't really believe in Node.js (Go  Haskell are our
 choices), so that is a small concern to us, but everyone has
 their failings.

The post is on the Joyent blog; but was written by someone from
MemCachier, a new partner with Joyent. MemCachier seems to have
partnered with a few other cloud platforms -- Heroku, for
example. It's nice to see a Bay Area cloud company speak up
for Haskell.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: [Haskell-cafe] Substituting values

2012-12-22 Thread Jason Dusek
2012/12/21 Radical radi...@google.com:
 Sometimes I'll need something like:

   if value == Foo then Bar else value

 Or some syntactic variation thereof:

   case value of { Foo - Bar; _ - value }

 Is there a better/shorter way to do it? I'm surprised that it's more
 complicated to substitute a value on its own than e.g. in a list, using
 filter. Or perhaps I'm missing the right abstraction?

Haskell doesn't offer a compact ternary operator or similar
construct. In some cases, a local definition and pattern guards
is appealing:

  {-# LANGUAGE PatternGuards #-}

  f value = ... value' ...
   where value' | Foo - value = Bar
| otherwise= value

This does not really have the intuitive of appeal that a
pattern matching ternary operator might, though:

  f value = ... (Foo - value ? Bar : value) ...

In Haskell, working with patterns generally is cleaner with
multiple lines and full indentation.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: [Haskell] Status of Haskell'?

2012-12-01 Thread Jason Dusek
2012/12/1 Tijn van der Zant robot...@gmail.com:
 I think that there is more to take into account.
 Haskell is growing as a language that people use to solve scientific and
 business problems. It is starting to become more of a working language,
 which is a very good thing of course. But this also means that Haskell
 should accommodate the people who are only working with it (not developing
 the language) and might not have a clue about the developers of the
 language. I'm somewhere in between where I love to read about the
 developments (this is my first post) and use it to program robots in my lab
 (besides some other languages).
 To accommodate the people who just want to use Haskell, we might have a
 super-pragma (as previously proposed) and for those gaining skill it should
 be possible to subtract pragmas until you have turned them all off and you
 can call yourself a Haskell guru. Mind you, I am not one of those, simply
 because I have to program in 5 languages for my work. For me, all those
 pragmas are not a matter of ugliness, but more an annoyance. For starters it
 is even worse. They ask questions such as: What do I turn on? Did I already
 find a good pragma tutorial? Why do I need to know about pragmas if it is
 already difficult to learn the language? By subtracting the pragmas (or
 turning them off) people can learn what they actually do and improve their
 code and their thinking about the language.
 Quite often I need the get something done, and due to time pressure I do not
 always have the luxury to make the code beautiful. And since it is Haskell
 (if it compiles it probably does what you want) I do not always care. For
 many users, pragmas are a Haskell concept that they can live without in the
 first part of their Haskell programming career (and they just turn a load of
 them on without even thinking about it what they do, but hey, the code works
 now!...)
 I think that we should accommodate the 'working programmers' and make their
 life a little bit easier, so that it becomes easier to start programming in
 Haskell and the language can be put to use by more people.
 This does not exclude having a 'pragma prime' that includes proposals for
 Haskell' of course. But it would help people starting with Haskell a lot
 imho.

Thank you for highlighting the many ways in which pragmas are
a problem from a practical point of view.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: [Haskell] Status of Haskell'?

2012-12-01 Thread Jason Dusek
2012/11/30 Gábor Lehel illiss...@gmail.com:
 Well, I'm not so sure it's a great idea to just bake what GHC
 does at this moment (for any particular extension) into the
 standard without really thinking about it. Even then, you have
 to figure out, in great detail, what GHC does, and write it
 all down! That's not negligible effort, either. And the
 alternative is to also publicly discuss and hash all of it out
 down to the little tiny gritty stuff. But wanting to write a
 new standard (big effort!) just to get rid of some pragmas and
 make people feel better (small payoff!) feels like a mismatch
 to me.

It is a large payoff, considering the thousands and thousands of
people that it creates a small payoff for: people writing
Haskell, people learning Haskell, people teaching Haskell. A
standard is a lot of effort for a handful of people.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: [Haskell] Status of Haskell'?

2012-12-01 Thread Jason Dusek
2012/12/1 Tijn van der Zant robot...@gmail.com:
 I think that there is more to take into account.
 Haskell is growing as a language that people use to solve scientific and
 business problems. It is starting to become more of a working language,
 which is a very good thing of course. But this also means that Haskell
 should accommodate the people who are only working with it (not developing
 the language) and might not have a clue about the developers of the
 language. I'm somewhere in between where I love to read about the
 developments (this is my first post) and use it to program robots in my lab
 (besides some other languages).
 To accommodate the people who just want to use Haskell, we might have a
 super-pragma (as previously proposed) and for those gaining skill it should
 be possible to subtract pragmas until you have turned them all off and you
 can call yourself a Haskell guru. Mind you, I am not one of those, simply
 because I have to program in 5 languages for my work. For me, all those
 pragmas are not a matter of ugliness, but more an annoyance. For starters it
 is even worse. They ask questions such as: What do I turn on? Did I already
 find a good pragma tutorial? Why do I need to know about pragmas if it is
 already difficult to learn the language? By subtracting the pragmas (or
 turning them off) people can learn what they actually do and improve their
 code and their thinking about the language.
 Quite often I need the get something done, and due to time pressure I do not
 always have the luxury to make the code beautiful. And since it is Haskell
 (if it compiles it probably does what you want) I do not always care. For
 many users, pragmas are a Haskell concept that they can live without in the
 first part of their Haskell programming career (and they just turn a load of
 them on without even thinking about it what they do, but hey, the code works
 now!...)
 I think that we should accommodate the 'working programmers' and make their
 life a little bit easier, so that it becomes easier to start programming in
 Haskell and the language can be put to use by more people.
 This does not exclude having a 'pragma prime' that includes proposals for
 Haskell' of course. But it would help people starting with Haskell a lot
 imho.

Thank you for highlighting the many ways in which pragmas are
a problem from a practical point of view.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: Status of Haskell'?

2012-12-01 Thread Jason Dusek
2012/11/30 Gábor Lehel illiss...@gmail.com:
 Well, I'm not so sure it's a great idea to just bake what GHC
 does at this moment (for any particular extension) into the
 standard without really thinking about it. Even then, you have
 to figure out, in great detail, what GHC does, and write it
 all down! That's not negligible effort, either. And the
 alternative is to also publicly discuss and hash all of it out
 down to the little tiny gritty stuff. But wanting to write a
 new standard (big effort!) just to get rid of some pragmas and
 make people feel better (small payoff!) feels like a mismatch
 to me.

It is a large payoff, considering the thousands and thousands of
people that it creates a small payoff for: people writing
Haskell, people learning Haskell, people teaching Haskell. A
standard is a lot of effort for a handful of people.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: [Haskell] Status of Haskell'?

2012-11-30 Thread Jason Dusek
2012/11/30 Gábor Lehel illiss...@gmail.com:
 Executive summary: We don't need a new standard right now. If
 people don't think it's worth their while to work on it,
 they're probably right. New, competing implementations might
 be valuable. If we have them, there will be demand for a
 standard, making decisions about it will be easier, and it
 will probably be better.

It would be nice for there to be a new standard so that many
features in GHC -- such as overloaded strings, rank n types,
MPTCs, c. -- were enabled by default without any pragmas.

This standardization process amounts to endorsement of existing
features which seems like not a bad process at all. It makes
the standard descriptive rather than predictive.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: Status of Haskell'?

2012-11-30 Thread Jason Dusek
2012/11/30 Gábor Lehel illiss...@gmail.com:
 Executive summary: We don't need a new standard right now. If
 people don't think it's worth their while to work on it,
 they're probably right. New, competing implementations might
 be valuable. If we have them, there will be demand for a
 standard, making decisions about it will be easier, and it
 will probably be better.

It would be nice for there to be a new standard so that many
features in GHC -- such as overloaded strings, rank n types,
MPTCs, c. -- were enabled by default without any pragmas.

This standardization process amounts to endorsement of existing
features which seems like not a bad process at all. It makes
the standard descriptive rather than predictive.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: [Haskell-cafe] Optimal line length for haskell

2012-10-30 Thread Jason Dusek
2012/10/29 MightyByte mightyb...@gmail.com:
 The ideal line length for text layout is based on the physiology of
 the human eye… At normal reading distance the arc of the visual field
 is only a few inches – about the width of a well-designed column of
 text, or about 12 words per line. Research shows that reading slows
 and retention rates fall as line length begins to exceed the ideal
 width, because the reader then needs to use the muscles of the eye and
 neck to track from the end of one line to the beginning of the next
 line. If the eye must traverse great distances on the page, the reader
 is easily lost and must hunt for the beginning of the next line.
 Quantitative studies show that moderate line lengths significantly
 increase the legibility of text.
 Web Style Guide – Basic Design Principles for Creating Website
 Patrick J. Lynch and Sarah Horton
 2nd edition, page 97.

Robert Bringhurst's The Elements of Typographic Style offers a
similar dictum:

  Anything from 45 to 75 characters is widely regarded as a
  satisfactory length of line for a single-column page set in a
  serifed text face in a text size. The 66-character line
  (counting both letters and spaces) is widely regarded as
  ideal. For multiple column work, a better average is 40 to 50
  characters.

   -- http://webtypography.net/Rhythm_and_Proportion/Horizontal_Motion/2.1.2/

I have come to accept 80 characters as a limit that is both in
keeping with programming convention and amenable to the good
taste of typographers. Many respectable software projects honor
this limit and to emulate them, in matters small as well as
large, is to simplify our work in many small ways. Art is long
and life is short.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: [Haskell-cafe] [Off-topic] How unimportant it is whether submarines can swim (EWD1056)

2012-10-27 Thread Jason Dusek
It is an interesting piece and I'm glad you went to the effort
to translate it.




- ...the question whether...

+ ...the question of whether or not...

To use could is to form either the past or the subjunctive.

Within a long sentence, we might prefer to contribute an article
on a topic as opposed to about a topic.

Burning is one of those things that is often taken to be all or
nothing; so equally burning is infelicitous. One could say
similarly burning or likewise burning to mean, it is also
burning.

So:

+ It has already been a few years or so ago now since the
+ editors of a somewhat obscure magazine asked me to contribute
+ an article on the question of whether or not computers can
+ think. I did not feel like doing that and I explained my
+ refusal with the remark that I found the suggested topic just
+ as unimportant as the similarly burning question of whether or
+ not submarines can swim.



It is hard to make the idiom reckoned on work in the
parenthetical passage; there are alternatives.

- I had reckoned without my host: the editor —a sociologist—
- wrote me back, that he found that last question very
- interesting as well!

+ I had not considered my audience: the editor -- a sociologist
+ -- wrote back, to say that he found the last question very
+ interesting as well!



with which popular believe - with which popular belief
As remarked by Gwern.



- A single factor of ten is already a difference between day and
- night...

+ A single factor of ten is like night and day...



It is important that an EM dash have spaces to both sides of it. For example:

- —in anthropomorphic terminology also called memory size—

+ -- in anthropomorphic terminology also called memory size --



One may use such as and like when providing examples; one
uses as and like when forming comparisons. (Icarus flew
like a bird. or Icarus flew as the birds do. but not Icarus
flew such as a bird.).

- The advantage of this poetic license is that it allows us to
- put an algebraic expression as (a+b)/c, a program fragment as
- x := x+1, and a decimal number like 729 all three under the
- same heading formula.

+ The advantage of this poetic license is that it allows us to
+ put an algebraic expression as (a+b)/c, a program fragment as
+ x := x+1, and a decimal number like 729 all three under the
+ same heading formula.



- Such a formal universe is therefore as novelty radical...

+ Such a formal universe is therefore a radical novelty...



- The most salient feature of the formal universe is, however,
- that nothing else than...

+ The most salient feature of the formal universe is, however,
+ that nothing other than...

+ The most salient feature of the formal universe, however, is
+ that nothing besides...



- Our traditional argues are mixed, viz. partly formal and
- partly verbal...

+ Our traditional ways of arguing are mixed, partly formal and
+ partly verbal...



- In that vision, a radical change of course in mathematics
- would leave in the long term footprints in the vast majority
- of our intellectual life.

+ In that vision, a radical change in mathematics would in time
+ leave an imprint in most areas of our intellectual life.



- I expect such a radical change of course.

+ I expect such a radical change, of course.




There would be a certain appropriateness in making the text more
Texan. The title would then be:

  It don't matter none whether subs can swim or not

but it'd really take a different American to see it through.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: [Haskell-cafe] Blocking IO FIFOs

2012-10-22 Thread Jason Dusek
Hi Everyone,

Thanks for all your help. I've put the first working version of
this on GitHub:

  https://github.com/solidsnack/coproc

Many improvements suggested in thread have not been implemented
as yet but I hope to integrate them as part of expanding the
tool to cover other interpreters, like Python or PSQL.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: [Haskell-cafe] Blocking IO FIFOs

2012-10-21 Thread Jason Dusek
2012/10/21 Donn Cave d...@avvanta.com:
 From Jason Dusek jason.du...@gmail.com:
 If I could somehow arrange to detect EOF when /tmp/exitpipe is
 closed, then I might as well redirect 1 and 2 to FIFOs and wait
 for them to EOF, collecting the output.

 However, all of my experiments suggest that there is simply no
 way in Haskell to detect the closing of the write end of a FIFO.
 With `openFileBlocking', one can detect when a FIFO is *opened*;
 but not when it is closed.

 [...] If I use POSIX I/O, it works fine.  So it looks to me
 like there is indeed a way in Haskell to detect a closed FIFO,
 it just may not be Haskell I/O without a lot more work ironing
 out the possible causes of failure.

Sadly, I can not do Posix IO on handles or read a ByteString
from a Posix FD.

 2) you need the named pipe only to detect command process
exit, and you can still apply Haskell I/O to the more
interesting data that accumulates in the command output
disk file.

Writing data to disk for communicating with other processes
is not a good pattern, I think.

 And there may be an answer for my problems with Haskell I/O.
 Could be as simple as using openFileBlocking, which apparently
 isn't supported in the ghc I'm using.  Could have something to
 do with the fine points of named pipes - for example, I
 believe you're supposed to open them O_RDWR in situations
 you'd think would call for O_READONLY.  (Though the latter
 worked for me with POSIX I/O.)

It is okay to open it O_READONLY if blocking when there is no
writer is acceptable. For this application, it is.

 While I'm here ... I share the concern expressed in an earlier
 followup about the outputs from bash in runInteractiveProcess.
 This looks like a feature of runInteractiveProcess that makes
 it intrinsically something like a code smell.  input-only
 and output-only processes are commonly used and fairly
 tractable, where input-output processes are unusual and and
 fragile, so it's an unfortunate convenience.  I think the idea
 is that you'd use createProcess specifying only the input
 redirection.

I am averse to adding just in case code that may not do
anything; too much system level code attains an air of mystery
this way.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


[Haskell-cafe] Blocking IO FIFOs

2012-10-20 Thread Jason Dusek
Hi all,

I am developing a coroutine-like interface to Bash.

  http://hpaste.org/76523

The idea is that one can send multiple queries to an
interpreter and then collect the results of each query. How do
we know when Bash is done with each query? Waiting for no more
output seems ambiguous; so the way CoBash works is:

  * Each query gets a tmp dir with two named pipes in it.
  * The query is wrapped in redirections to the pipes.
  * The pipes are removed when the query completes.

This does work, sort of:

  +Prelude :load CoBash.hs
  [1 of 1] Compiling CoBash   ( CoBash.hs, interpreted )
  Ok, modules loaded: CoBash.
  *CoBash tuple@(i,o,e,p) - start
  e :: Handle
  i :: Handle
  o :: Handle
  p :: ProcessHandle
  tuple :: (Handle, Handle, Handle, ProcessHandle)
  *CoBash query tuple for n in {1..4}; do sleep 1; echo $n; done
  (1\n2\n3\n4\n,)
  it :: (ByteString, ByteString)

I say sort of because it is quite brittle. Many commands do not
return at all, for example:

  *CoBash query tuple uname -a

The way I retrieve the output from the FIFOs seems dangerous:

  (,) $ Bytes.hGetContents oh * Bytes.hGetContents eh

Surely, the FIFO for STDERR can not be read from until the FIFO
for STDOUT is finished; but if there is a great deal of error
output then the process will fill the FIFO's buffer and get
stuck. If we switch the order of the reads, the for n in ...
example above blocks:

  (,) $ Bytes.hGetContents eh * Bytes.hGetContents oh

I have tried a few different ways to read from the two handles
concurrently; for example, by giving each thread an MVar
to put the contents in, or by using hGetNonBlocking on a list of
handles in a loop. Using the latter method, I never get EOF; it
just collects empty strings forever.

For comparison's sake, the expect behaviour with FIFOs is:

  In the first terminal:

   :; mkfifo fifo
   :; cat  fifo
a
b
c
d
^D
   :;

  In the second terminal:

   :; cat  fifo
a
b
c
d
   :;

Here I open the FIFO for reading with  while opening it for
writing with . As long as the writer writes, the reader reads;
when the writer closes the write end of the pipe, the reader
receives EOF. Trying to duplicate the read behaviour in Haskell,
using hGetContents from GHCi while using cat to write to the
FIFO, doesn't work; which seems a little bogus.

There have a been a few past threads about FIFOs and their
troublesome interaction with Haskell's async-by-default IO
style. To switch to System.Posix for IO -- and deal with Ptr
Word8, in order to handle binary data -- seems like an awful
step down.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B




{-# LANGUAGE OverloadedStrings
   , ScopedTypeVariables
   , ParallelListComp
   , TupleSections #-}

module CoBash where

import   Control.Applicative
import   Control.Concurrent
import   Control.Concurrent.MVar
import   Control.Exception
import   Control.Monad
import   Data.Bits
import   Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString.Char8 as Bytes
import   Data.Maybe
import   Data.Monoid
import qualified GHC.IO.Handle.FD
import   System.IO
import   System.IO.Error
import   System.Process
import   System.Posix.ByteString

import   System.IO.Temp

import qualified Text.ShellEscape as Esc


start :: IO (Handle, Handle, Handle, ProcessHandle)
start = runInteractiveProcess bash [] Nothing (Just [])

query :: (Handle, Handle, Handle, ProcessHandle) - ByteString
  - IO (ByteString, ByteString)
query (i, _, _, _) query = withFIFOs query'
 where query' ofo efo = do
 Bytes.hPut i cmd
 hFlush i
 [oh, eh] - mapM openFIFO [ofo, efo]
 (,) $ Bytes.hGetContents oh * Bytes.hGetContents eh -- Works.
--   (,) $ Bytes.hGetContents eh * Bytes.hGetContents oh -- Blocks.
where cmd = Bytes.unlines [{, query, } 1  ofo   2  efo]

shutdown :: (Handle, Handle, Handle, ProcessHandle) - IO ()
shutdown (i, _, _, p) = () $ hClose i * waitForProcess p


openFIFO path = GHC.IO.Handle.FD.openFileBlocking (Bytes.unpack path) ReadMode

-- | Run an IO action with two FIFOs in scope, which will removed after it
--   completes.
withFIFOs :: (RawFilePath - RawFilePath - IO a) - IO a
withFIFOs m = withSystemTempDirectory cobash. m'
 where m'   = (uncurry m =) . mk . Bytes.pack
   mk d = (o, e) $ (createNamedPipe o mode  createNamedPipe e mode)
where (o, e) = (d  /o, d  /e)
  mode   = ownerReadMode .|. ownerWriteMode .|. namedPipeMode

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


Re: [Haskell-cafe] Blocking IO FIFOs

2012-10-20 Thread Jason Dusek
2012/10/20 Asten, W.G.G. van (Wilfried, Student M-CSC)
w.g.g.vanas...@student.utwente.nl:
 Would you be happy with a solution like this:

  - First create two handles to two files in the tmp directory
  - Then use StdStream's UseHandle to redirect std_err and std_out
 (using CreatePipe for std_in) to these files
  - Then write your query to the Handle for std_in
  - waitForProcess
  - Collect std_out and std_err from the temporary files.

 If that is not satisfactory you may want to check out conduit-process
 (http://hackage.haskell.org/packages/archive/process-conduit/0.5.0.2/doc/html/src/Data-Conduit-Process.html#conduitProcess)
 that also does some interaction with a process and interleaves std_in
 and std_out.  It should not be to hard to combine std_err into that
 concept. I also faced this same problem and in one case solved it by
 using a temporary file to hold my content which was also deleted
 afterwards (This immediately prevented the content building up in
 memory).

For my application, it's important to be able to run multiple
queries against the same Bash session. Waiting for Bash to shut
down is thus not a viable way to finalize the response.

Perhaps I can spawn two cats with their outputs connected to the
FIFOs and wait for them to terminate.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: [Haskell-cafe] Blocking IO FIFOs

2012-10-20 Thread Jason Dusek
2012/10/20 Wilfried van Asten sniperrifle2...@gmail.com:
 Perhaps an interleaving solution as in process-conduit is
 still viable:

  - Check if one or both of the fifo's are still ready (Based
on your statement about the reading end receiving EOF
hIsEOF should work here). If both fifos are done the query
is finished so break the loop.

Alas, checking for EOF does not work. I mentioned this in
passing in my prior email; the code was somewhat involved and I
have deleted it. Here is a simple example of something that does
not work as expected:

  In the first terminal:

   :; mkfifo fifo
   :; ghci
--  :m + GHC.IO.Handle.FD System.IO
--  do { h - openFileBlocking fifo ReadMode ; hGetContents h }

  In the second terminal, *after* doing everything in the first
  terminal:

   :; cat  fifo
 type some characters here 
^D

Notice that the characters appear in the first terminal, as the
output of hGetContents. Sending ^D to end cat does not register
any effect in GHCi; hGetContents dutifully waits and you can in
fact run cat on the FIFO again to send more characters to the
same instances of hGetContents. This would seem to be due to
non-blocking IO, deep in the IO manager.

  - Check if some output is available on oh. If so read some of
it. Repeat.

  - Otherwise check if some output is available on eh. If so
read some of it. Repeat loop

 I also see you don't do anything with the std_out and std_err
 pipes of bash as given by runInteractiveProcess. These could
 also cause a problem even when the FIFO's are working
 correctly. Replace these by handles to the null file or let
 the output be dumped on the parent's std_in and std_out
 (StdStream Inherit).

I would prefer to leave them be, since they're passed in from
the caller, who nominally owns them. If you mean that I should
close them in `start', well, that would make it hard to debug
this stuff; and if I simply tie them to the parent's file
descriptors, it will make it hard to deal with more than a few
CoBashes at one time while testing.

Using cat to read the FIFOs and allowing Haskell to read from
cat does work, actually.

  https://gist.github.com/3923673

Shell really is such a nice language for tying together
processes.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B




{-# LANGUAGE OverloadedStrings
   , ScopedTypeVariables
   , ParallelListComp
   , TupleSections #-}

module CoBash where

import   Control.Applicative
import   Control.Concurrent
import   Control.Concurrent.MVar
import   Control.Exception
import   Control.Monad
import   Data.Bits
import   Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString.Char8 as Bytes
import   Data.Maybe
import   Data.Monoid
import qualified GHC.IO.Handle.FD
import   System.IO
import   System.IO.Error
import   System.Process
import   System.Posix.ByteString

import   System.IO.Temp

import qualified Text.ShellEscape as Esc


start :: IO (Handle, Handle, Handle, ProcessHandle)
start = runInteractiveProcess bash [] Nothing (Just [])

query :: (Handle, Handle, Handle, ProcessHandle) - ByteString
  - IO (ByteString, ByteString)
query (i, _, _, _) query = withFIFOs query'
 where query' ofo efo = do
 Bytes.hPut i cmd
 hFlush i
 [ob, eb] - backgroundReadFIFOs [ofo, efo]
 return (ob, eb)
where cmd = Bytes.unlines [{, query, } 1  ofo   2  efo]

shutdown :: (Handle, Handle, Handle, ProcessHandle) - IO ()
shutdown (i, _, _, p) = () $ hClose i * waitForProcess p


openFIFO path = GHC.IO.Handle.FD.openFileBlocking (Bytes.unpack path) ReadMode

-- | Run an IO action with two FIFOs in scope, which will removed after it
--   completes.
withFIFOs :: (RawFilePath - RawFilePath - IO a) - IO a
withFIFOs m = withSystemTempDirectory cobash. m'
 where m'   = (uncurry m =) . mk . Bytes.pack
   mk d = (o, e) $ (createNamedPipe o mode  createNamedPipe e mode)
where (o, e) = (d  /o, d  /e)
  mode   = ownerReadMode .|. ownerWriteMode .|. namedPipeMode

drainFIFO :: ByteString - IO ByteString
drainFIFO path = do
  (i, o, e, p) - bash [-c, exec cat (Bytes.unpack path)]
  hClose i
  hClose e
  Bytes.hGetContents o * waitForProcess p

backgroundReadFIFOs theFIFOs = do
  cells - sequence (newEmptyMVar $ theFIFOs)
  sequence_ [ forkIO (drainFIFO p = putMVar c) | p - theFIFOs | c - cells ]
  sequence (takeMVar $ cells)

bash args = runInteractiveProcess bash args Nothing (Just [])

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


Re: [Haskell-cafe] Blocking IO FIFOs

2012-10-20 Thread Jason Dusek
2012/10/20 Donn Cave d...@avvanta.com:
 Quoth Jason Dusek jason.du...@gmail.com,
 ...
 For my application, it's important to be able to run multiple
 queries against the same Bash session. Waiting for Bash to shut
 down is thus not a viable way to finalize the response.

 You could redirect to disk files and also use a pipe to wait for exit.

 I suppose you redirect I/O for individual queries by applying shell
 redirections to the command?  So like this,

uname -a  /tmp/cmd1 2 /tmp/cmd2 7 /tmp/exitpipe

 ... then read from /tmp/exitpipe, ignore empty result and read command
 outputs from the disk files.

If I could somehow arrange to detect EOF when /tmp/exitpipe is
closed, then I might as well redirect 1 and 2 to FIFOs and wait
for them to EOF, collecting the output.

However, all of my experiments suggest that there is simply no
way in Haskell to detect the closing of the write end of a FIFO.
With `openFileBlocking', one can detect when a FIFO is *opened*;
but not when it is closed.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: [Haskell-cafe] Getting PID of a child process

2012-10-19 Thread Jason Dusek
2012/10/19 Donn Cave d...@avvanta.com:
 Quoth Jason Dusek jason.du...@gmail.com,

 Using `System.Process.runInteractiveProcess', I can start a process
 and get a handle to it:

   runInteractiveProcess
:: FilePath
- [String]
- Maybe FilePath
- Maybe [(String, String)]
- IO (Handle, Handle, Handle, ProcessHandle)

 For diagnostic purposes, I'd like to print the PID of the
 process attached to this handle -- how best to do that?


 There's a good chance this isn't the best way, but it seems to work:


 import System.Process
 import System.Process.Internals (ProcessHandle__(..), PHANDLE, 
 withProcessHandle)

 -- for use with withProcessHandle
 getPID :: ProcessHandle__ - IO (ProcessHandle__, Maybe PHANDLE)
 getPID h@(OpenHandle t) = return (h, Just t)
 getPID h@(ClosedHandle t) = return (h, Nothing)

 main = do
 (h0, h1, h2, hp) - runInteractiveProcess /bin/date [] Nothing 
 Nothing
 mp - withProcessHandle hp $ getPID
 print mp

 Seems like more scaffolding than this application really ought to require.

It seems wrong that in the definition of ProcessHandle__, the PID is not
recoverable once the process has exited. I wonder if this has something
to do with Windows compatibility.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


[Haskell-cafe] Getting PID of a child process

2012-10-18 Thread Jason Dusek
Hi All,

Using `System.Process.runInteractiveProcess', I can start a process
and get a handle to it:

  runInteractiveProcess
   :: FilePath
   - [String]
   - Maybe FilePath
   - Maybe [(String, String)]
   - IO (Handle, Handle, Handle, ProcessHandle)

For diagnostic purposes, I'd like to print the PID of the
process attached to this handle -- how best to do that?

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: [Haskell-cafe] Partial statical linking

2012-09-26 Thread Jason Dusek
Hi,

I made a mistake when I said this worked, earlier. My experiment
was run on a system where I had implemented Christian Maeder's
suggestion, by symlinking some static libs in to GHC's libdir.
Naturally, everything appeared to work.

It turns out we have to pass the libraries with -optl, to
prevent GHC from reordering them relative to the other linker
options we've passed.

  ghc -outputdir ./tmp --make -O2 sssp.hs -o sssp.ubuntu \
   -optl-Wl,--whole-archive \
-optl/usr/lib/x86_64-linux-gnu/libffi.a \
-optl/usr/lib/x86_64-linux-gnu/libgmp.a \
-optl/usr/lib/x86_64-linux-gnu/libz.a \
   -optl-Wl,--no-whole-archive

The next great discovery in this area could be an automated, and
general, way of generating the static libraries list. At
present, what I have to do is:

 1. compile the executable once with plain `ghc --make',

 2. use `ldd' to find shared libraries used by this executable
and correlate these with debs use `dpkg -S',

 3. throw away shared libraries that are part of the `libc'
Debian package,

 4. find the corresponding `.a' files for each `.so', use find
and some Sed trickery and

 5. construct the appropriate linker linker before compiling
everything again.

I could probably skip recompiling everything in step 5 and just
relink. I've made steps 2, 3 and 4 into a shell script that
could be easily adapted to other projects:

  https://github.com/erudify/sssp/blob/master/ubuntu/util

I wonder how much of this we could legitimately ask GHC to do
for us. Statically linking every C dependency is unwise -- it's
not supposed to work to link libc and its immediate dependencies
-- and it does seem odd to ask that GHC have knowledge of this.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B


2012/9/24 Jason Dusek jason.du...@gmail.com:
 2012/9/19 Brandon Allbery allber...@gmail.com:
 On Wed, Sep 19, 2012 at 7:06 AM, Jason Dusek jason.du...@gmail.com wrote:
 What I attempted was building a binary with only some C libraries
 statically linked, with this command line:

   # Build https://github.com/erudify/sssp on Ubunut 12.04
   ghc -outputdir ./tmp -v --make -O2 sssp.hs -o sssp.ubuntu \
 /usr/lib/x86_64-linux-gnu/libffi.a \
 /usr/lib/x86_64-linux-gnu/libgmp.a \
 /usr/lib/x86_64-linux-gnu/libz.a

 However, this really made no difference. Running `ldd' on the
 resulting binary reveals that libz and friends are still
 dynamically linked:

 On Linux you probably need -optl--whole-archive for this to do anything;
 alternately, you would need to get the final ld command line out of ghc and
 insert the above libraries into it *after* the package .a files.

 Putting them before the packages (including the GHC runtime) that need them,
 as will happen by default, will cause them to be ignored because they
 contain no required symbols *at that point* in the link.  --whole-archive
 tells to blindly link the whole static archive in instead of ignoring it.

 Hi Brandon,

 This turned out to be the right ticket. The full command line is
 like this:

   ghc -outputdir ./tmp --make -O2 sssp.hs -o sssp.ubuntu \
 -optl-Wl,--whole-archive \
   /usr/lib/x86_64-linux-gnu/libffi.a \
   /usr/lib/x86_64-linux-gnu/libgmp.a \
   /usr/lib/x86_64-linux-gnu/libz.a \
 -optl-Wl,--no-whole-archive

 Without the --no-whole-archive at the end, I get errors like:

   (.text+0x880): multiple definition of `__morestack_unblock_signals'
   
 /usr/lib/gcc/x86_64-linux-gnu/4.6/libgcc.a(generic-morestack.o):(.text+0x880):
 first defined here
   /usr/lib/gcc/x86_64-linux-gnu/4.6/libgcc.a(generic-morestack.o): In
 function `__morestack_allocate_stack_space':

 I am not sure why that happens -- libgcc.a wasn't explicitly
 asked for; but it stands to reason that one shouldn't specify
 --whole-archive for everything GHC links, just the archives of
 interest. Life is short and art is long.

 --
 Jason Dusek
 pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: [Haskell-cafe] Partial statical linking

2012-09-24 Thread Jason Dusek
2012/9/19 Brandon Allbery allber...@gmail.com:
 On Wed, Sep 19, 2012 at 7:06 AM, Jason Dusek jason.du...@gmail.com wrote:
 What I attempted was building a binary with only some C libraries
 statically linked, with this command line:

   # Build https://github.com/erudify/sssp on Ubunut 12.04
   ghc -outputdir ./tmp -v --make -O2 sssp.hs -o sssp.ubuntu \
 /usr/lib/x86_64-linux-gnu/libffi.a \
 /usr/lib/x86_64-linux-gnu/libgmp.a \
 /usr/lib/x86_64-linux-gnu/libz.a

 However, this really made no difference. Running `ldd' on the
 resulting binary reveals that libz and friends are still
 dynamically linked:

 On Linux you probably need -optl--whole-archive for this to do anything;
 alternately, you would need to get the final ld command line out of ghc and
 insert the above libraries into it *after* the package .a files.

 Putting them before the packages (including the GHC runtime) that need them,
 as will happen by default, will cause them to be ignored because they
 contain no required symbols *at that point* in the link.  --whole-archive
 tells to blindly link the whole static archive in instead of ignoring it.

Hi Brandon,

This turned out to be the right ticket. The full command line is
like this:

  ghc -outputdir ./tmp --make -O2 sssp.hs -o sssp.ubuntu \
-optl-Wl,--whole-archive \
  /usr/lib/x86_64-linux-gnu/libffi.a \
  /usr/lib/x86_64-linux-gnu/libgmp.a \
  /usr/lib/x86_64-linux-gnu/libz.a \
-optl-Wl,--no-whole-archive

Without the --no-whole-archive at the end, I get errors like:

  (.text+0x880): multiple definition of `__morestack_unblock_signals'
  /usr/lib/gcc/x86_64-linux-gnu/4.6/libgcc.a(generic-morestack.o):(.text+0x880):
first defined here
  /usr/lib/gcc/x86_64-linux-gnu/4.6/libgcc.a(generic-morestack.o): In
function `__morestack_allocate_stack_space':

I am not sure why that happens -- libgcc.a wasn't explicitly
asked for; but it stands to reason that one shouldn't specify
--whole-archive for everything GHC links, just the archives of
interest. Life is short and art is long.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: [Haskell-cafe] Partial statical linking

2012-09-19 Thread Jason Dusek
2011/12/1 Irene Knapp ireney.kn...@gmail.com:
 The typical trick to force GHC to statically link a C library
 is to give the full path to the .a of it as one of the object
 files in the GHC invocation that does the final linking.  This
 means you don't need any -l or -L flags pertaining to that
 library.  Some libraries are very particular about the order
 you list them in when doing this, but I don't really
 understand the issues there.  You usually will also have to
 chase dependencies by hand and list them in the same fashion.

I recently tried using this method to create static binary; but
I was not able to get it to work. I thought I would revive this
old thread and see if anyone else has given it a shot.

What I attempted was building a binary with only some C libraries
statically linked, with this command line:

  # Build https://github.com/erudify/sssp on Ubunut 12.04
  ghc -outputdir ./tmp -v --make -O2 sssp.hs -o sssp.ubuntu \
/usr/lib/x86_64-linux-gnu/libffi.a \
/usr/lib/x86_64-linux-gnu/libgmp.a \
/usr/lib/x86_64-linux-gnu/libz.a

However, this really made no difference. Running `ldd' on the
resulting binary reveals that libz and friends are still
dynamically linked:

  ldd sssp.ubuntu
  linux-vdso.so.1 =  (0x7fff94253000)
  libz.so.1 = /lib/x86_64-linux-gnu/libz.so.1 (0x7f0ddfdbb000)
  libpthread.so.0 = /lib/x86_64-linux-gnu/libpthread.so.0
(0x7f0ddfb9e000)
  libgmp.so.10 = /usr/lib/x86_64-linux-gnu/libgmp.so.10
(0x7f0ddf92f000)
  libffi.so.6 = /usr/lib/x86_64-linux-gnu/libffi.so.6
(0x7f0ddf727000)
  libm.so.6 = /lib/x86_64-linux-gnu/libm.so.6 (0x7f0ddf42d000)
  librt.so.1 = /lib/x86_64-linux-gnu/librt.so.1 (0x7f0ddf224000)
  libdl.so.2 = /lib/x86_64-linux-gnu/libdl.so.2 (0x7f0ddf02)
  libc.so.6 = /lib/x86_64-linux-gnu/libc.so.6 (0x7f0ddec63000)
  /lib64/ld-linux-x86-64.so.2 (0x7f0ddffdb000)

There is always -optl-static which, nowadays, results in a
truly static executable; but it leads to a lot of warnings, too.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: [Haskell-cafe] Partial statical linking

2012-09-19 Thread Jason Dusek
2012/9/19 Christian Maeder christian.mae...@dfki.de:
 I usually just copy those .a files (that should be linked statically) into
 `ghc --print-libdir`.

Wow, it worked! But this isn't the sort of change I'd to a user's
system that I'd like to encode in a Makefile...

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: [Haskell-cafe] Why so many strings in Network.URI, System.Posix and similar libraries?

2012-03-14 Thread Jason Dusek
2012/3/12 Jeremy Shaw jer...@n-heptane.com:
 On Sun, Mar 11, 2012 at 1:33 PM, Jason Dusek jason.du...@gmail.com wrote:
 Well, to quote one example from RFC 3986:

  2.1.  Percent-Encoding

   A percent-encoding mechanism is used to represent a data octet in a
   component when that octet's corresponding character is outside the
   allowed set or is being used as a delimiter of, or within, the
   component.

 Right. This describes how to convert an octet into a sequence of characters,
 since the only thing that can appear in a URI is sequences of characters.

 The syntax of URIs is a mechanism for describing data octets,
 not Unicode code points. It is at variance to describe URIs in
 terms of Unicode code points.


 Not sure what you mean by this. As the RFC says, a URI is defined entirely
 by the identity of the characters that are used. There is definitely no
 single, correct byte sequence for representing a URI. If I give you a
 sequence of bytes and tell you it is a URI, the only way to decode it is to
 first know what encoding the byte sequence represents.. ascii, utf-16, etc.
 Once you have decoded the byte sequence into a sequence of characters, only
 then can you parse the URI.

Mr. Shaw,

Thanks for taking the time to explain all this. It's really
helped me to understand a lot of parts of the URI spec a lot
better. I have deprecated my module in the latest release

  http://hackage.haskell.org/package/URLb-0.0.1

because a URL parser working on bytes instead of characters
stands out to me now as a confused idea.

--
Jason Dusek
pgp  ///  solidsnack  1FD4C6C1 FED18A2B

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


Re: [Haskell-cafe] Why so many strings in Network.URI, System.Posix and similar libraries?

2012-03-11 Thread Jason Dusek
2012/3/11 Jeremy Shaw jer...@n-heptane.com:
 Also, URIs are not defined in terms of octets.. but in terms
 of characters.  If you write a URI down on a piece of paper --
 what octets are you using?  None.. it's some scribbles on a
 paper. It is the characters that are important, not the bit
 representation.

Well, to quote one example from RFC 3986:

  2.1.  Percent-Encoding

   A percent-encoding mechanism is used to represent a data octet in a
   component when that octet's corresponding character is outside the
   allowed set or is being used as a delimiter of, or within, the
   component.

The syntax of URIs is a mechanism for describing data octets,
not Unicode code points. It is at variance to describe URIs in
terms of Unicode code points.

 If you render a URI in a utf-8 encoded document versus a
 utf-16 encoded document.. the octets will be different, but
 the meaning will be the same. Because it is the characters
 that are important. For a URI Text would be a more compact
 representation than String.. but ByteString is a bit dodgy
 since it is not well defined what those bytes represent.
 (though if you use a newtype wrapper around ByteString to
 declare that it is Ascii, then that would be fine).

This is all fine well and good for what a URI is parsed from
and what it is serialized too; but once parsed, the major
components of a URI are all octets, pure and simple. Like the
host part of the authority:

  host= IP-literal / IPv4address / reg-name
  ...
  reg-name= *( unreserved / pct-encoded / sub-delims )

The reg-name production is enough to show that, once the host
portion is parsed, it could contain any bytes whatever.
ByteString is the only correct representations for a parsed host
and userinfo, as well as a parsed path, query or fragment.

--
Jason Dusek
pgp  ///  solidsnack  1FD4C6C1 FED18A2B

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


Re: [Haskell-cafe] Why so many strings in Network.URI, System.Posix and similar libraries?

2012-03-11 Thread Jason Dusek
2012/3/11 Brandon Allbery allber...@gmail.com:
 On Sun, Mar 11, 2012 at 14:33, Jason Dusek jason.du...@gmail.com wrote:
  The syntax of URIs is a mechanism for describing data octets,
  not Unicode code points. It is at variance to describe URIs in
  terms of Unicode code points.

 You might want to take a glance at RFC 3492, though.

RFC 3492 covers Punycode, an approach to internationalized
domain names. The relationship of RFC 3986 to the restrictions
on the syntax of host names, as given by the DNS, is not simple.
On the one hand, we have:

   This specification does not mandate a particular registered
   name lookup technology and therefore does not restrict the
   syntax of reg-name beyond what is necessary for
   interoperability.

The production for reg-name is very liberal about allowable
octets:

  reg-name= *( unreserved / pct-encoded / sub-delims )

However, we also have:

  The reg-name syntax allows percent-encoded octets in order to
  represent non-ASCII registered names in a uniform way that is
  independent of the underlying name resolution technology.
  Non-ASCII characters must first be encoded according to
  UTF-8...

The argument for representing reg-names as Text is pretty strong
since the only representable data under these rules is, indeed,
Unicode code points.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: [Haskell-cafe] Why so many strings in Network.URI, System.Posix and similar libraries?

2012-03-11 Thread Jason Dusek
2012/3/11 Thedward Blevins thedw...@barsoom.net:
 On Sun, Mar 11, 2012 at 13:33, Jason Dusek jason.du...@gmail.com wrote:
  The syntax of URIs is a mechanism for describing data octets,
  not Unicode code points. It is at variance to describe URIs in
  terms of Unicode code points.

 This claim is at odds with the RFC you quoted:

 2. Characters

 The URI syntax provides a method of encoding data, presumably for the sake
 of identifying a resource, as a sequence of characters. The URI characters
 are, in turn, frequently encoded as octets for transport or presentation.
 This specification does not mandate any particular character encoding for
 mapping between URI characters and the octets used to store or transmit
 those characters.

 (Emphasis is mine)

 The RFC is specifically agnostic about serialization. I generally agree that
 there are a lot of places where ByteString should be used, but I'm not
 convinced this is one of them.

Hi Thedward,

I am CC'ing the list since you raise a good point that, I think,
reflects on the discussion broadly. It is true that intent of
the spec is to allow encoding of characters and not of bytes: I
misread its intent, attending only to the productions. But due
to the way URIs interact with character encoding, a general URI
parser is constrained to work with ByteStrings, just the same.

The RFC ...does not mandate any particular character encoding
for mapping between URI characters and the octets used to store
or transmit those characters... and in Section 1.2.1 it is
allowed that the encoding of may depend on the scheme:

   In local or regional contexts and with improving technology, users
   might benefit from being able to use a wider range of characters;
   such use is not defined by this specification.  Percent-encoded
   octets (Section 2.1) may be used within a URI to represent characters
   outside the range of the US-ASCII coded character set if this
   representation is allowed by the scheme or by the protocol element in
   which the URI is referenced.

It seems possible for any octet, 0x00..0xFF, to show up in a
URI, and it is only after parsing the scheme that we can say
whether the octet belongs there are not. Thus a general URI
parser can only go as far as splitting into components and
percent decoding before handing off to scheme specific
validation rules (but that's a big help already!). I've
implemented a parser under these principles that handles
specifically URLs:

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

Although the intent of the spec is to represent characters, I
contend it does not succeed in doing so. Is it wise to assume
more semantics than are actually there? The Internet and UNIX
are full of broken junk; but faithful representation would seem
to be better than idealization for those occasions where we must
deal with them. I'm not sure the assumption of textiness
really helps much in practice since the Universal Character Set
contains control codes and bidi characters -- data that isn't
really text.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: [Haskell-cafe] Why so many strings in Network.URI, System.Posix and similar libraries?

2012-03-11 Thread Jason Dusek
2012/3/12 Jeremy Shaw jer...@n-heptane.com:
  The syntax of URIs is a mechanism for describing data octets,
  not Unicode code points. It is at variance to describe URIs in
  terms of Unicode code points.

 Not sure what you mean by this. As the RFC says, a URI is defined entirely
 by the identity of the characters that are used. There is definitely no
 single, correct byte sequence for representing a URI. If I give you a
 sequence of bytes and tell you it is a URI, the only way to decode it is to
 first know what encoding the byte sequence represents.. ascii, utf-16, etc.
 Once you have decoded the byte sequence into a sequence of characters, only
 then can you parse the URI.

Hmm. Well, I have been reading the spec the other way around:
first you parse the URI to get the bytes, then you use encoding
information to interpret the bytes. I think this curious passage
from Section 2.5 is interesting to consider here:

   For most systems, an unreserved character appearing within a URI
   component is interpreted as representing the data octet corresponding
   to that character's encoding in US-ASCII.  Consumers of URIs assume
   that the letter X corresponds to the octet 01011000, and even
   when that assumption is incorrect, there is no harm in making it.  A
   system that internally provides identifiers in the form of a
   different character encoding, such as EBCDIC, will generally perform
   character translation of textual identifiers to UTF-8 [STD63] (or
   some other superset of the US-ASCII character encoding) at an
   internal interface, thereby providing more meaningful identifiers
   than those resulting from simply percent-encoding the original
   octets.

I am really not sure how to interpret this. I have been reading
'%' in productions as '0b00100101' and I have written my parser
this way; but that is probably backwards thinking.

 ...let's say we have the path segments [foo, bar/baz] and we wish to use
 them in the path info of a URI. Because / is a special character it must be
 percent encoded as %2F. So, the path info for the url would be:

  foo/bar%2Fbaz

 If we had the path segments, [foo,bar,baz], however that would be
 encoded as:

  foo/bar/baz

 Now let's look at decoding the path. If we simple decode the percent encoded
 characters and give the user a ByteString then both urls will decode to:

  pack foo/bar/baz

 Which is incorrect. [foo, bar/baz] and [foo,bar,baz] represent
 different paths. The percent encoding there is required to distinguish
 between to two unique paths.

I read the section on paths differently: a path is sequence of
bytes, wherein slash runs are not permitted, among other rules.
However, re-reading the section, a big todo is made about
hierarchical data and path normalization; it really seems your
interpretation is the correct one. I tried it out in cURL, for
example:

  http://www.ietf.org/rfc%2Frfc3986.txt # 404 Not Found
  http://www.ietf.org/rfc/rfc3986.txt   # 200 OK

My recently released released URL parser/pretty-printer is
actually wrong in its handling of paths and, when corrected,
will only amount to a parser of URLs that are encoded in
US-ASCII and supersets thereof.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


[Haskell-cafe] Why so many strings in Network.URI, System.Posix and similar libraries?

2012-03-10 Thread Jason Dusek
The content of URIs is defined in terms of octets in the RFC,
and all Posix interfaces are byte streams and C strings, not
character strings. Yet in Haskell, we find these objects exposed
with String interfaces:

 :info Network.URI.URI
data URI
  = URI {uriScheme :: String,
 uriAuthority :: Maybe URIAuth,
 uriPath :: String,
 uriQuery :: String,
 uriFragment :: String}
-- Defined in Network.URI

 :info System.Posix.Env.getEnvironment
System.Posix.Env.getEnvironment :: IO [(String, String)]
-- Defined in System.Posix.Env

But there is no law that environment variables must be made of
characters:

 :; export x=$'\xFF' ; echo -n $x | xxd -p
  ff
 :; locale
  LANG=en_US.UTF-8

That the relationship between bytes and characters can be
confusing, both in working with UNIX and in dealing with web
protocols, is undeniable -- but it seems unwise to limit the
options available to Haskell programmers in dealing with these
systems.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: [Haskell-cafe] Partial statical linking

2011-12-20 Thread Jason Dusek
One thing I don't get is how, for GHC on Mac, this seems to work
with out any fiddling at all; but on Linux it's really quite
challenging.

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments



2011/12/1 Irene Knapp ireney.kn...@gmail.com:
 Please note that when we build with in-tree GMP, we statically link it into 
 libHSinteger-GMP.a.  Also, again only with in-tree, we patch it first to use 
 our allocator.  Both of these things are to make life easier for users 
 creating hybrid Haskell/C executables who need to use GMP from the C side, 
 which is possible only by linking in a second copy of it.

 The typical trick to force GHC to statically link a C library is to give the 
 full path to the .a of it as one of the object files in the GHC invocation 
 that does the final linking.  This means you don't need any -l or -L flags 
 pertaining to that library.  Some libraries are very particular about the 
 order you list them in when doing this, but I don't really understand the 
 issues there.  You usually will also have to chase dependencies by hand and 
 list them in the same fashion.

 Good luck!

 Sent from my iPhone

 On Dec 1, 2011, at 3:08 AM, Edward Z. Yang ezy...@mit.edu wrote:

 libgmp and libffi are external libraries not associated with
 Haskell, so I don't think -static (which is for Haskell libraries)
 applies to them.  You'll have the same problem with any other
 sort of library of this type, like libdl and friends ;-)

 Edward

 Excerpts from Jason Dusek's message of Sat Nov 26 01:59:18 -0500 2011:
 Some time ago, I wrote to this list about making shared
 libraries with GHC, in such a way that the RTS was linked and
 ready to go. Recently, I've been looking a similar but, in a
 sense, opposite problem: linking Haskell executables with some
 of their non-Haskell dependencies, for distribution.

 I tried passing a few different sets of options to the linker
 through GHC, with -optl:

  -optl'-Wl,-r'
  -optl'-Wl,-r,-dy'
  -optl'-Wl,-static,-lffi,-lgmp,-dy'

 None of these had the desired effect. In the end, running GHC
 with -v and carefully editing the linker line produced the
 desired change (I have linked to and provided the diff below).

 The effect -optl seems to be to introduce options in the linker
 line just before -lHSrtsmain, which would seem to prevent one
 from linking libffi and libgmp differently. Is editing and
 storing away the linker script the best option at present for
 partially static linking?

 --
 Jason Dusek
 ()  ascii ribbon campaign - against html e-mail
 /\  www.asciiribbon.org   - against proprietary attachments




 https://github.com/solidsnack/arx/commit/90ec5efdb0e991344aa9a4ad29456d466e022c3e
 #@@ -122,10 +122,8 @@
 #   -lHSarray-0.3.0.2 \
 #   -lHSbase-4.3.1.0 \
 #   -lHSinteger-gmp-0.2.0.3 \
 #-  -lgmp \
 #   -lHSghc-prim-0.2.0.0 \
 #   -lHSrts \
 #-  -lffi \
 #   -lm \
 #   -lrt \
 #   -ldl \
 #@@ -136,4 +134,7 @@
 #   -lgcc_s --no-as-needed \
 #   /usr/lib/gcc/x86_64-linux-gnu/4.6.1/crtend.o \
 #   /usr/lib/gcc/x86_64-linux-gnu/4.6.1/../../../x86_64-linux-gnu/crtn.o \
 #+  -static \
 #+  -lgmp \
 #+  -lffi \


 ___
 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] If you'd design a Haskell-like language, what would you do different?

2011-12-20 Thread Jason Dusek
Support for long binary data sections would be nice.

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments

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


[Haskell-cafe] Partial statical linking

2011-11-25 Thread Jason Dusek
Some time ago, I wrote to this list about making shared
libraries with GHC, in such a way that the RTS was linked and
ready to go. Recently, I've been looking a similar but, in a
sense, opposite problem: linking Haskell executables with some
of their non-Haskell dependencies, for distribution.

I tried passing a few different sets of options to the linker
through GHC, with -optl:

  -optl'-Wl,-r'
  -optl'-Wl,-r,-dy'
  -optl'-Wl,-static,-lffi,-lgmp,-dy'

None of these had the desired effect. In the end, running GHC
with -v and carefully editing the linker line produced the
desired change (I have linked to and provided the diff below).

The effect -optl seems to be to introduce options in the linker
line just before -lHSrtsmain, which would seem to prevent one
from linking libffi and libgmp differently. Is editing and
storing away the linker script the best option at present for
partially static linking?

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments




https://github.com/solidsnack/arx/commit/90ec5efdb0e991344aa9a4ad29456d466e022c3e
#@@ -122,10 +122,8 @@
#   -lHSarray-0.3.0.2 \
#   -lHSbase-4.3.1.0 \
#   -lHSinteger-gmp-0.2.0.3 \
#-  -lgmp \
#   -lHSghc-prim-0.2.0.0 \
#   -lHSrts \
#-  -lffi \
#   -lm \
#   -lrt \
#   -ldl \
#@@ -136,4 +134,7 @@
#   -lgcc_s --no-as-needed \
#   /usr/lib/gcc/x86_64-linux-gnu/4.6.1/crtend.o \
#   /usr/lib/gcc/x86_64-linux-gnu/4.6.1/../../../x86_64-linux-gnu/crtn.o \
#+  -static \
#+  -lgmp \
#+  -lffi \

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


Re: [Haskell-cafe] ST not strict enough?

2011-11-17 Thread Jason Dusek
2011/11/16 Johan Tibell johan.tib...@gmail.com:
 On Wed, Nov 16, 2011 at 2:23 PM, Jason Dusek jason.du...@gmail.com wrote:
 Tried a modifySTRef' defined this way:

 modifySTRef' ref f           =  do
  val                       -  (f $!!) $ readSTRef ref
  writeSTRef ref (val `seq` val)

 ...but there was no change in memory usage.

 Why not just

     modifySTRef :: STRef s a - (a - a) - ST s ()
     modifySTRef ref f = do
         x - readSTRef ref
         writeSTRef ref $! f x

 (Note that I didn't check if modifySTRef was actually a problem in this
 case).

I just didn't want to miss an opportunity to put in extra
strictness annotations! School of redundancy school.

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments

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


Re: [Haskell-cafe] ST not strict enough?

2011-11-17 Thread Jason Dusek
2011/11/16 Tristan Ravitch travi...@cs.wisc.edu:
 Have you tried building the vector using things besides
 write/ST? It might be a bit faster to use something like
 Vector.unfoldr or Vector.generateM and ByteString.index to
 build up a pure Vector. After that you could use
 Vector.unsafeThaw to convert that pure Vector into an MVector.

I tried unfoldrN and, indeed, the memory usage has gone down.
Residency seems to be 45K, regardless of input size; and the
productivity is above 90% even for small (128K) inputs. Thanks
for your suggestion.

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments

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


Re: [Haskell-cafe] ST not strict enough?

2011-11-16 Thread Jason Dusek
2011/11/15 Roman Cheplyaka r...@ro-che.info:
 * Jason Dusek jason.du...@gmail.com [2011-11-15 20:08:48+]
 I'm having some trouble with memory usage in rebuilding a
 ByteString with some sequences escaped. I thought I'd try
 vectors. However, it seems that even a relatively simple
 function, one that places all the bytes of a ByteString in to a
 vector, uses a great deal of memory.

 I think what's happening here is ByteString's strictness makes things
 actually lazy on your side.

 Namely, unpack function produces its result strictly, whole list at
 once. As a result, the resulting list cannot be consumed one-by-one,
 so it takes memory. You see ST thunks because

  mapM_ f as =  sequence_ (map f as)

 and that map probably gets fused with unpack.

 I guess the proper solution here is to use lazy bytestring and make sure
 the chunks are not very big.

Hi Roman,

Switching to the lazy ByteStrings API does, indeed, help; total
memory usage is around 16M. I will have a look at the rules that
are fired to see what I can learn.

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments

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


Re: [Haskell-cafe] ST not strict enough?

2011-11-16 Thread Jason Dusek
2011/11/15 Johan Tibell johan.tib...@gmail.com:
 On Tue, Nov 15, 2011 at 12:08 PM, Jason Dusek jason.du...@gmail.com wrote:
 Should I be annotating my functions with strictness, for the
 vector reference, for example? Should I be using STUArrays,
 instead?

 From
 http://www.haskell.org/ghc/docs/latest/html/libraries/base-4.4.1.0/Control-Monad-ST-Safe.html

     The = and  operations are strict in the state (though not in values
 stored in the state).

 which implies that

  modifySTRef counter (+1)

 is too lazy.

As a first cut at strictifying the ST operations, I introduced a
strict plus and strict vector write operation, strictifying
every parameter that admitted it.

  (+!) a b   =  ((+) $!! a) $!! b
  w v n b = (Vector.unsafeWrite v $!! n) $!! b

This did not alter memory usage in any noticeable way. (Tried it
with strict and lazy ByteStrings and both had the same memory
usage as they did without the extra strictness.)

It does seem off odd that building a vector byte by byte is so
hard to do performantly. Maybe the memory usage ends up being
okay when working with larger structures, though.

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments




diff --git a/Rebuild.hs b/Rebuild.hs
@@ -15,6 +15,7 @@ import Data.STRef
 import Data.String
 import Data.Word

+import Control.DeepSeq
 import Data.Vector.Unboxed (Vector)
 import qualified Data.Vector.Unboxed as Vector (create, length)
 import qualified Data.Vector.Unboxed.Mutable as Vector hiding (length)
@@ -46,8 +47,8 @@ rebuildAsVector bytes=  byteVector
 n   -  readSTRef counter
 return (Vector.unsafeSlice 0 n v)
   writeOneByte v counter b   =  do n - readSTRef counter
-   Vector.unsafeWrite v n b
+   w v n b
modifySTRef counter (+!1)
+  (+!) a b   =  ((+) $!! a) $!! b
+  w v n b = (Vector.unsafeWrite v $!! n) $!! b

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


Re: [Haskell-cafe] ST not strict enough?

2011-11-16 Thread Jason Dusek
2011/11/16 Johan Tibell johan.tib...@gmail.com:
 On Wed, Nov 16, 2011 at 12:07 PM, Johan Tibell johan.tib...@gmail.com wrote:
 +! doesn't work unless modifySTRef is already strict in the result of the
 function application. You need to write modifySTRef' that seq:s the result
 of the function application before calling writeSTRef.

 Just double checked. modifySTRef is too lazy:
 -- |Mutate the contents of an 'STRef'
 modifySTRef :: STRef s a - (a - a) - ST s ()
 modifySTRef ref f = writeSTRef ref . f = readSTRef ref
 We need Data.STRef.Strict

Tried a modifySTRef' defined this way:

modifySTRef' ref f   =  do
  val   -  (f $!!) $ readSTRef ref
  writeSTRef ref (val `seq` val)

...but there was no change in memory usage.

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments

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


[Haskell-cafe] ST not strict enough?

2011-11-15 Thread Jason Dusek
Hi All,

I'm having some trouble with memory usage in rebuilding a
ByteString with some sequences escaped. I thought I'd try
vectors. However, it seems that even a relatively simple
function, one that places all the bytes of a ByteString in to a
vector, uses a great deal of memory.

I've pulled this function out into a mini-module for testing:

  https://github.com/solidsnack/arx/blob/ST/Rebuild.hs#L37

On a one megabyte input, it peaks at ~38M of memory:

  :;  dd if=/dev/zero bs=1M count=1 | ./rebuildprof +RTS -s
  ...
38,724,208 bytes maximum residency (5 sample(s))
 1,983,720 bytes maximum slop
76 MB total memory in use (0 MB lost due to fragmentation)
  ...
%GC time  61.3%  (61.5% elapsed)

A heap profile by type, with -hy, shows a linear rise in ST
items -- up to ~26M -- and then a linear decrease. It would
stand to reason that, with sufficient strictness, the memory
allocated to ST would stay constant and small.

Should I be annotating my functions with strictness, for the
vector reference, for example? Should I be using STUArrays,
instead?

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments

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


Re: [Haskell-cafe] Waiting on input with `hWaitForInput' or `threadWaitRead'

2011-10-18 Thread Jason Dusek
2011/10/18 Ertugrul Soeylemez e...@ertes.de:
 A proxy server acts a lot like an echo server.  The difference is that
 usually before the actual proxying starts you have a negotiation phase,
 and instead of echoing back to the same socket, you just write it to a
 different one.  Here is an (untested) example:

    (clientH, clientHost, clientPort) - accept serverSock
    destH - negotiate clientH
    doneVar - newEmptyMVar

    forkIO (hGetContents clientH = hPutStr destH = putMVar doneVar)
    forkIO (hGetContents destH = hPutStr clientH = putMVar doneVar)
    replicateM_ 2 (takeMVar doneVar)
    mapM_ hClose [clientH, destH]

This code seems like it says:

  Allow the client to write to the server one time.

  Allow the server to write to the client one time.

  Teardown both sides of the connection.

Am I reading this correctly? This is, indeed, a proxy; but I'm
not sure it could support a wide range of protocols.

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments

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


Re: [Haskell-cafe] Waiting on input with `hWaitForInput' or `threadWaitRead'

2011-10-18 Thread Jason Dusek
2011/10/18 Gregory Collins g...@gregorycollins.net:
 On Tue, Oct 18, 2011 at 3:18 AM, Jason Dusek jason.du...@gmail.com wrote:
  The lazy bridging code, `lazyBridge', blocks (unsurprisingly)
  and does not allow packets to go back and forth. I think I need
  explicit selects/waits here to get the back and forth traffic.
  Maybe there is a some way to leverage GHC's internal async I/O
  but I'm not sure how to do it.

 Maybe: forkIO two threads, one for the read end, one for the write
 end? I would use a loop over lazy I/O, also.

This does work, thanks; the new version of lazyBridge is:


  lazyBridge  ::  Handle - Handle - IO ()
  lazyBridge a b   =  do forkIO (flush a b)
 forkIO (flush b a)
 return ()
   where
flush a b  =  LazyB.hGetContents a = LazyB.hPut b

  -- http://hpaste.org/52814

I am kind of surprised that this works at all, actually.

The strict version has this problem where it lets each socket
takes turns sending and receiving, if you try to send and it's
not your turn, it waits for the other one to send before sending
your data. The lazy version just sends bytes as they become
available, the desired behaviour.

I guess if I wanted to instrument the proxying, to keep a tally
of how much traffic there was (to GC little used connections,
for example), I would need to move up to enumerators?

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments

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


Re: [Haskell-cafe] Waiting on input with `hWaitForInput' or `threadWaitRead'

2011-10-18 Thread Jason Dusek
2011/10/18 Jason Dusek jason.du...@gmail.com:
 2011/10/18 Ertugrul Soeylemez e...@ertes.de:
  A proxy server acts a lot like an echo server.  The difference is that
  usually before the actual proxying starts you have a negotiation phase,
  and instead of echoing back to the same socket, you just write it to a
  different one.  Here is an (untested) example:
 
     (clientH, clientHost, clientPort) - accept serverSock
     destH - negotiate clientH
     doneVar - newEmptyMVar
 
     forkIO (hGetContents clientH = hPutStr destH = putMVar doneVar)
     forkIO (hGetContents destH = hPutStr clientH = putMVar doneVar)
     replicateM_ 2 (takeMVar doneVar)
     mapM_ hClose [clientH, destH]

 This code seems like it says: [...]

After working through Gregory Collins suggestion, above, I see
that I was not reading your code correctly.

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments

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


[Haskell-cafe] Waiting on input with `hWaitForInput' or `threadWaitRead'

2011-10-17 Thread Jason Dusek
I would like to use evented I/O for a proxying application. My
present thinking is to fork a thread for each new connection and
then to wait for data on either socket in this thread, writing
to one or the other socket as needed.

There are two API functions I've found for waiting and they each
raise some questions:

  System.IO.hWaitForInput :: Handle - Int - IO Bool

This function dovetails well with the high-level networking
libraries but introduces difficulties because it decodes the
stream to check for full characters. If the handle is set to
binary mode, are decoding errors still a possibility?

  Control.Concurrent.threadWaitRead :: Fd - IO ()

This function would seem to be closer to the ideal in terms
of performance and semantics: it just waits until there are
bytes available. However, converting the handle produced by
the high-level networking libraries to a file descriptor
closes the handle (!). This makes some sense: plucking the
descriptor out of a handle doubtless interacts with other
users of that handle in an unsafe way. It seems I need to
through a very different set of libraries, one based on file
descriptors and not handles, to be able to use this
function.

Ideally, I'd get something like select() on handles, just saying
whether there are bytes or not. However, I haven't managed to
find anything like that in the standard libraries.

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments

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


Re: [Haskell-cafe] Waiting on input with `hWaitForInput' or `threadWaitRead'

2011-10-17 Thread Jason Dusek
2011/10/17 Ertugrul Soeylemez e...@ertes.de:
 Jason Dusek jason.du...@gmail.com wrote:
 I would like to use evented I/O for a proxying application.
 My present thinking is to fork a thread for each new
 connection and then to wait for data on either socket in this
 thread, writing to one or the other socket as needed.

 [...]

 Ideally, I'd get something like select() on handles, just
 saying whether there are bytes or not. However, I haven't
 managed to find anything like that in the standard libraries.

 I don't think you want either of the functions you mentioned.
 What you probably want instead is to do concurrent
 programming by creating Haskell threads.  A hundred Haskell
 threads reading from Handles are translated to one or more OS
 threads using whatever polling mechanism (select(), poll(),
 epoll) your operating system supports.

 I have uploaded a simple concurrent echo server implementation
 to hpaste [1]. It uses one thread for the stdout logger, one
 thread for the server, one thread for each client and finally
 a main thread waiting for you to hit enter to quit the
 application.

 [1] http://hpaste.org/52742 - Concurrent echo server with logger

I am not sure how to apply the principle you mention to a proxy,
which must read from and write to both handles in turn (or,
ideally, as needed).

Here's a little demo that uses hWaitForInput and strict
ByteStrings as well as plain hGetContents with lazy ByteStrings:

  http://hpaste.org/52777

You can load it in GHC and try out the strict/hWaitForInput
version like this:

   proxy (PortNumber 9001) (PortNumber 9000) strictBridge

Then run, in this order, in two terminals:

 :; nc -l -k 9000  # The proxied backend server.
 :; nc localhost 9001  # The nominal client.

Now you can type text on the client side, hit return and see it
on the server side and then vice versa.

The lazy bridging code, `lazyBridge', blocks (unsurprisingly)
and does not allow packets to go back and forth. I think I need
explicit selects/waits here to get the back and forth traffic.
Maybe there is a some way to leverage GHC's internal async I/O
but I'm not sure how to do it.

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments

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


Re: [Haskell-cafe] Waiting on input with `hWaitForInput' or `threadWaitRead'

2011-10-17 Thread Jason Dusek
2011/10/18 Jason Dusek jason.du...@gmail.com:
 ...load it in GHC and...

s/GHC/GHCi/

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


[Haskell-cafe] Locking, unsafePerformIO and bolt-on thread safety.

2011-05-09 Thread Jason Dusek
  A friend is making bindings to a C library that offers some
  fast math operations. The normal way to use the library is
  like this:

int a = ...; int b = ...; int c = ...; int d = ...;
int x=  ...;
int m, n;
create_lookup_table(x);
m=  perform_math(a, b, x);
n=  perform_math(c, d, x);

  We see that the lookup table for x must be created before we
  can perform math in the field/ring/what-have-you defined by x.
  Once we have created the table, though, we're done.

  My friend would like to create a pure interface to this
  library. One thought was to write an interface to perform_math
  that checked if the table was created, created it if not, and
  did all this while locking an MVar so that no other instance
  could be called at the same time, trashing the table. Doing
  this behind unsafePerformIO would seem to be the ticket.

  We end up with an implementation like this:

module FastMath where

import Control.Concurrent
import Foreign
import Foreign.C


foreign import ccall create_lookup_table :: CInt - IO ()
foreign import ccall perform_math :: CInt - CInt - CInt - IO CInt

masterLock   =  unsafePeformIO (newMVar [CInt])

safe_perform_math a b x  =  do
  list  -  takeMVar masterLock
  toPut -  if not (x `elem` list)
  then do create_lookup_table x
  return (x:list)
  elsereturn list
  result-  perform_math a b x
  putMVar masterLock toPut
  return result

performMath a b x = unsafePerformIO (safe_perform_math a b x)

  This does not compile but I think it gets the point across. Is
  this approach safe? The unsafePerformIO in conjunction with
  locking has me worried.

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments

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


Re: [Haskell-cafe] Python is lazier than Haskell

2011-04-28 Thread Jason Dusek
On Thu, Apr 28, 2011 at 07:19, Gracjan Polak gracjanpo...@gmail.com wrote:
 Sometimes I wish for a -fphp flag that would turn some type
 errors into warnings.
 [...]
 GHC could substitute 'y = error Couldn't match expected type
 `[a]' against inferred type `()'' and compile anyway.

  PHP doesn't really do dynamic type errors, though. To be more
  like PHP, the -fphp flag should surely coerce y to a list,
  using read and show if possible and otherwise using
  unsafeCoerce.

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments

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


[Haskell-cafe] Killing threads in foreign calls.

2011-04-17 Thread Jason Dusek
  I am building an application that uses Postgres for storage.
  If a query runs too long, I would like to kill the querying
  thread, releasing its lock on the connection; if the
  connection is a in a bad state -- for example, busy -- I would
  like to clean up the connection.

  Unfortunately, killing calls in to libpq seems not to work. I
  have put a minimal example on hpaste:

http://hpaste.org/45774/minimal_pg_contention_example

  If you install libpq with Cabal, you can run it. In the
  example, the main thread spawns a worker thread that queries
  Postgres, running SELECT pg_sleep(10);; the main thread
  waits half a second and then tries to kill the worker.
  Unfortunately, the worker always manages to get as far as
  printing complete.

  In the code, I call `Database.PQ.exec':


http://hackage.haskell.org/packages/archive/libpq/0.4.1/doc/html/src/Database-PQ.html#exec

  This in turn calls a `safe' binding, `c_PQexec', to `PQexec'
  in the C library:


http://hackage.haskell.org/packages/archive/libpq/0.4.1/doc/html/src/Database-PQ.html#line-

  There are async interfaces, too; they do not seem to be any
  more killable then the sync ones.

  Maybe the problem is that you can't kill a thread while it's
  in a foreign call? I do not see any documentation to this
  effect; but I may have missed it.

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments

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


Re: [Haskell-cafe] Killing threads in foreign calls.

2011-04-17 Thread Jason Dusek
On Sun, Apr 17, 2011 at 20:26, Edward Z. Yang ezy...@mit.edu wrote:
 This is a fairly nontrivial problem.  First off, let me tell you
 what you do not /actually/ want to happen: you don't want the OS
 level thread performing the foreign call to actually be killed...

  From this I gather, one can not generally kill Haskell threads
  while they are in the midst of foreign calls. I guess
  interrupting execution to terminate the program is special
  since you don't expect anything to work properly afterward.

 If the asynchronous API has the ability to cancel a query given
 some handler, you instead want to set up a custom kill thread function
 that checks if a thread has an active query and then performs
 another FFI call to perform that cancellation.

  It turns out the PGcancel exists for this purpose. Is it safe
  and reasonable to make query cancellation a ThreadKilled
  handler in the query thread?

  I gather I need to write the busy loop for polling for data in
  Haskell. Although libpq has a procedure -- PGgetResult -- that
  polls for data, it would not respond to killThread.

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments

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


Re: [Haskell-cafe] [Haskell] Linker flags for foreign export.

2011-03-13 Thread Jason Dusek
  I have managed to get both static and dynamic to work on
  Ubuntu; and I've set aside a repo on Github to collect notes
  on this stuff as I work out building on various systems.

https://github.com/solidsnack/hso

  I need rpath for the dynamic-dynamic case on Ubuntu:

ghc -shared -dynamic -o libfoo.dynamic-dynamic.so \
Foo.o Foo_stub.o fooinit.o \
-L/usr/lib/ghc-6.12.1 \
-optl-Wl,-rpath,/usr/lib/ghc-6.12.1 \
-lHSrts-ghc6.12.1

  The linker options in both cases could be derived
  automagically from ghc-pkg, I think.

  I've set aside dynamic-static for now (not sure what use it
  would be). It turns out there is a simpler way to write
  Foo_init:

extern void __stginit_Foo(void);
static void Foo_init (void) __attribute__ ((constructor));
void Foo_init (void) {
  int argc = 1;
  char *arg = ;
  char **argv = arg;
  hs_init(argc, argv);
  hs_add_root(__stginit_Foo);
}

  Is there any case in which the empty string would be unsafe?

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments

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


Re: [Haskell-cafe] [Haskell] Linker flags for foreign export.

2011-03-11 Thread Jason Dusek
  I now have it working for static-static on Linux; but not with
  dynamic anything yet. Thanks for all your help.

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments

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


Re: [Haskell-cafe] [Haskell] Linker flags for foreign export.

2011-03-09 Thread Jason Dusek
On Tue, Mar 8, 2011 at 08:23, Max Bolingbroke
batterseapo...@hotmail.com wrote:
 On 8 March 2011 05:28, Jason Dusek jason.du...@gmail.com wrote:
    gcc -g -Wall -O2 -fPIC -Wall -o import \
      -I/usr/lib/ghc-6.12.1/include/ \
      import.c exports.so

 In my experience, the easiest way to do this is to use gcc to build
 object files from C source files, and then specify those object files
 on the ghc command line in order to get GHC to do the linking step.
 This will deal with linking in the correct RTS and, if you specify
 appropriate -package flags, dependent packages as well.

 If you want a C main function then see user guide section 8.2.1.1 at
 http://www.haskell.org/ghc/docs/latest/html/users_guide/ffi-ghc.html.

  Following your advice, I was able to get a working main,
  linking the .o's (no attempt at an SO this time) with GHC.
  However, what I was hoping to do was build an SO and that
  could be linked without GHC, for example via Postgres's
  LANGUAGE C functionality (load SOs and run them) or Ruby's
  DL/Import (same idea for Ruby). Requiring GHC for linking
  would really frustrate that goal :)

  Is there a tutorial I should be following? Well-Typed's blog
  post on this in the early days of shared object support seemed
  to be doing what I was doing.

--
Jason Dusek
Linux User #510144 | http://counter.li.org/

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


Re: [Haskell-cafe] [Haskell] Linker flags for foreign export.

2011-03-09 Thread Jason Dusek
  I've gleaned a little bit of useful info from looking at what
  GHC spits out with -v; I found that ordering the libraries in
  the way they do it makes one of my undefined symbols
  (`hs_free_stable_ptr') go away.

  However, my library ends up with a couple undefined
  __stginit_* symbols which prevent it from loading. I thought
  this might be a symptom of building Foo.o from Foo.hs with
  -dynamic; and indeed, building it without the -dynamic flag
  gives me an SO with many, many __stginit_* functions defined
  in it; but that SO causes the loader to segfault (both Ruby's
  DL/Import and my little test program).

  I'm trying to hew relatively close to Duncan Coutts'
  blog posting in working through this; so I have different
  code and a new Makefile:


https://github.com/solidsnack/bash/tree/0e93b6aed7971886c12b95646e5baadc40fe62bc/hs/well-typed

  The three different permutations of SOs -- fully dynamic,
  fully static and hybrid -- each fail to load differently:

:;  ./loadfoo ./libfoo.dynamic-dynamic.so
 trying to load ./libfoo.dynamic-dynamic.so
 .so load error:
/usr/lib/ghc-6.12.1/base-4.2.0.0/libHSbase-4.2.0.0-ghc6.12.1.so:
undefined symbol: forkOS_createThread
:;  ./loadfoo ./libfoo.static-static.so
 trying to load ./libfoo.static-static.so
Segmentation fault
:;  ./loadfoo ./libfoo.dynamic-static.so
 trying to load ./libfoo.dynamic-static.so
 .so load error: ./libfoo.dynamic-static.so: undefined symbol:
__stginit_base_Prelude_dyn

  The little tester program, `loadfoo', is drawn from the blog
  post's example; Ruby's DL/Import fails the same way in each
  case.

  It would be pretty nice to demo an easy way to load and work
  with Haskell functions from Ye Olde Favorite Language. Seems
  like SOs for the masses will have to wait a little bit,
  though.

--
Jason Dusek
Linux User #510144 | http://counter.li.org/

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


[Haskell] Linker flags for foreign export.

2011-03-07 Thread Jason Dusek
  I am having no luck generating a foreign export and calling it
  from C. The problem seems to be that I must spoon feed the linker.
  My working example is the files under this directory on Github:


https://github.com/solidsnack/bash/tree/106e4de8358a726984d54859fb0b4aeaf264156f/hs/exports

  Running `make' to produce the executable that imports the
  binding yields a number of unresolved linkages:

:;  make import
ghc --make -fPIC -dynamic -c exports.hs
[1 of 1] Compiling LanguageBashExports ( exports.hs, exports.o )
ghc -shared exports.o exports_stub.o -o exports.so \
  -L/usr/lib/ghc-6.12.1/ -lHSrts \
  -L/usr/lib/ghc-6.12.1/ghc-prim-0.2.0.0/ -lHSghc-prim-0.2.0.0 \
  -L/usr/lib/ghc-6.12.1/integer-gmp-0.2.0.0/ -lHSinteger-gmp-0.2.0.0 \
  -L/usr/lib/ghc-6.12.1/base-4.2.0.0/ -lHSbase-4.2.0.0 \
  -lffi
gcc -g -Wall -O2 -fPIC -Wall -o import \
  -I/usr/lib/ghc-6.12.1/include/ \
  import.c exports.so
exports.so: undefined reference to `timer_settime'
exports.so: undefined reference to `__stginit_base_DataziWord_dyn'
exports.so: undefined reference to `clock_gettime'
exports.so: undefined reference to `__stginit_base_Prelude_dyn'
exports.so: undefined reference to `__stginit_base_ForeignziCziTypes_dyn'
exports.so: undefined reference to `timer_delete'
exports.so: undefined reference to `timer_create'
exports.so: undefined reference to `hs_free_stable_ptr'
collect2: ld returned 1 exit status
make: *** [import] Error 1

  If I add linker directives for libHSrts and librt to the
  compilation of import.c, the only unresolved symbols remaining
  are the STG init functions for the Prelude, Data.Word and
  Foreign.C.Types:

:;  make import
gcc -g -Wall -O2 -fPIC -Wall -o import \
  -I/usr/lib/ghc-6.12.1/include/ \
  import.c exports.so \
  -L/usr/lib/ghc-6.12.1/ -lHSrts \
  -lrt
exports.so: undefined reference to `__stginit_base_DataziWord_dyn'
exports.so: undefined reference to `__stginit_base_Prelude_dyn'
exports.so: undefined reference to `__stginit_base_ForeignziCziTypes_dyn'
collect2: ld returned 1 exit status
make: *** [import] Error 1

  This hide and go seek with symbols really makes me feel like
  I'm just doing it wrong, though. I linked exports.so
  statically so why shouldn't it include `hs_free_stable_ptr'
  already (as well as the stginit functions)? Not sure why I
  need to mention librt at this step and not at the previous
  one. The truth is, I don't write C very often and in fact I am
  only doing this to create a bridge to Ruby.

  How should I be approaching this? Is there an SO-chasing
  option?

--
Jason Dusek
Linux User #510144 | http://counter.li.org/

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


[Haskell-cafe] ANN: bash-0.0.0

2011-03-05 Thread Jason Dusek
  Many-a-time, have I used higher level languages to generate
  Bash scripts. Here, for the first time, I have taken the time
  to write a structured and safe Bash pretty printer, leveraging
  some work on shell escaping I did some months ago.


http://hackage.haskell.org/packages/archive/bash/0.0.0/doc/html/Language-Bash.html

  A wide range of Bash constructs are supported. It's easiest to
  point out what's not supported at present:

 .  Arithmetic substitutions (those within $(( ))).

 .  Bash's test special form (using [[ ]]). Ordinary uses of
the test command are of course fully supported.

 .  Specialized expression de-referencing forms that allow
substitution and substring selection; the only thing
supported in this domain is defaulting and length:

  ${#var}   # Length of var in bytes.
  ${var:-}  # If var is not set, yield the empty string.

  Many other forms that are tedious to get right -- special
  variable names, array expansions, even eval -- are fully
  supported.

  I'll be using this tool to support a config generation system.
  Another interesting application is generating Bash completion
  scripts.

  If you decide to use it and have trouble please let me know;
  this is the first Language.Something that I have written and
  it may not present the friendliest interface. Do let me know,
  also, if the omitted syntactic structures would be helpful to
  you and I will see what I can do to include them.

--
Jason Dusek
Linux User #510144 | http://counter.li.org/

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


Re: [Haskell-cafe] ANN: bash-0.0.0

2011-03-05 Thread Jason Dusek
On Sun, Mar 6, 2011 at 04:27, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:
 Maybe this could be integrated with language-sh [1] to get parsing
 support as well?

 [1]: http://hackage.haskell.org/package/language-sh

  It's hard to say without testing it; but anything labeled Sh
  probably won't parse real Bash very well.

  Would parsing a subset be enough? There are certain kinds of
  unescaped variable references that I don't plan to support in
  the Syntax; so there'd be nothing to parse them in to. Maybe I
  will have to rethink this part; I considered a

Quoted (Expression t)

  constructor for Expression. A real parser should probably
  preserve comments, too.

  It is normal to include parsers in Language.Something modules;
  in this particular case, I assumed Bash analysis would not be
  used much. If you are interested in a way to wrap Bash you
  pull out of a file into a script you construct with the
  Syntax, you might try the Language.Bash.Annotations.Lines
  datatype.

--
Jason Dusek
Linux User #510144 | http://counter.li.org/

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


Re: [Haskell-cafe] Thoughts on program annotations.

2011-03-04 Thread Jason Dusek
On Fri, Mar 4, 2011 at 07:01, wren ng thornton w...@freegeek.org wrote:
 where the annotation of MergeAnn is merged with the previous
 annotation up the tree (via mappend), thus allowing for
 annotations to be inherited and modified incrementally based
 on the Monoid instance; whereas the NewAnn constructor uses
 the annotation directly, overriding any contextual
 annotations. This can be helpful to reduce the amount of
 duplication in the AST, though how helpful will depend on how
 you plan to use/generate the ASTs.

  To handle this situation, I thought I'd leave it in the hands
  of the user (who will be me later) to use Data.Foldable.fold
  (or not) to arrive at the annotation when building up their
  tree of statements. I don't anticipate a problem with this but
  I may not use monoidal annotations on this AST for some time.
  (I anticipate using comments and raw text inclusions in the
  near future.)

--
Jason Dusek
Linux User #510144 | http://counter.li.org/

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


[Haskell-cafe] Thoughts on program annotations.

2011-03-03 Thread Jason Dusek
  Hi List,

  I am working on a Bash config generation system. I've decided
  to factor out the Bash AST and pretty printer, here in a
  pre-release state:

https://github.com/solidsnack/bash

  One thing I'd like to support is generic annotations, so that
  at a future time I can add (and render) comments, mark
  subscripts with what privilege (package install, sudo) they
  require or otherwise characterize the script outside its
  lexical structure. I ended up making my statement type a
  Functor with a Foldable instance.

  Given that every statement has an annotation, it seemed better
  to me to use mutually recursive datatypes, using one datatype
  to capture annotatedness, like this:

--  From 
https://github.com/solidsnack/bash/blob/c718de36d349efc9ac073a2c7082742c45606769/hs/Language/Bash/Syntax.hs

data Annotated t = Annotated t (Statement t)
data Statement t = SimpleCommand Expression [Expression]
 | ...
 | IfThen (Annotated t) (Annotated t)
 | ...

  I wonder what folks think of this approach? It does mean I end
  up with all leaf-level annotations being potentially without
  annotations; this allows for relatively generic definitions,
  on the one hand; but forces type annotations at the use-site
  in many cases. It also means I have mutually recursive Functor
  and Foldable instances.

  Another option for annotations would be a sort of tree of
  zippers pointing in to the statement tree; this seems horrible
  at first glance since it leaves open the question of how the
  annotations are associated with their nodes in the first
  place. However, it does have the nice feature of simplifying
  the type of statements and also is just much more modular
  feeling.

  What does the list think?

--
Jason Dusek
Linux User #510144 | http://counter.li.org/

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


Re: [Haskell] [Haskell-cafe] ANN: unordered-containers - a new, faster hashing-based containers library

2011-02-18 Thread Jason Dusek
  What are your thoughts on iterative construction of maplike
  datastructures? Could something like builder work for maps,
  too? In the project I'm working on, I have a function that
  receives a bunch of YAML fragments and builds a big YAML map
  out of them.

--
Jason Dusek
Linux User #510144 | http://counter.li.org/

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


Re: [Haskell-cafe] ANN: unordered-containers - a new, faster hashing-based containers library

2011-02-18 Thread Jason Dusek
  What are your thoughts on iterative construction of maplike
  datastructures? Could something like builder work for maps,
  too? In the project I'm working on, I have a function that
  receives a bunch of YAML fragments and builds a big YAML map
  out of them.

--
Jason Dusek
Linux User #510144 | http://counter.li.org/

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


[Haskell-cafe] Haskell wiki admins -- who are they?

2011-02-04 Thread Jason Dusek
  I am having some trouble getting in to my account on
  the Haskell wiki. I requested a password ~24 hours
  ago reset but have not received the email yet. Who
  should I contact about this?

--
Jason Dusek
Linux User #510144 | http://counter.li.org/

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


[Haskell-cafe] Finite but not fixed length...

2010-10-13 Thread Jason Dusek
  Is there a way to write a Haskell data structure that is
  necessarily only one or two or seventeen items long; but
  that is nonetheless statically guaranteed to be of finite
  length?

--
Jason Dusek
Linux User #510144 | http://counter.li.org/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Finite but not fixed length...

2010-10-13 Thread Jason Dusek
  Thanks everyone for your thoughtful replies. I might have
  expected a referral to a paper; it's a pleasant surprise
  to have these worked examples.

--
Jason Dusek
Linux User #510144 | http://counter.li.org/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Finite but not fixed length...

2010-10-13 Thread Jason Dusek
2010/10/13 Jonas Almström Duregård jonas.dureg...@chalmers.se:
 ...and you can always do

 hack :: Vec n a - FixedVec a
 hack x :: FixedVec undefined

 Also I'm guessing 1, 2 and 17 are just examples, he really wants arbitrary
 length finite lists.

  Indeed. Where I said is necessarily I meant is not necessarily.

--
Jason Dusek
Linux User #510144 | http://counter.li.org/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ByteString missing rewrite RULES (zipWith' f a = pack . zipWith f a)

2010-10-05 Thread Jason Dusek
On Tue, Oct 5, 2010 at 18:07, Thomas DuBuisson
thomas.dubuis...@gmail.com wrote:
 If not, perhaps we could make chunkOverhead = max 16 (2 *
 sizeOf (undefined ::Int)) so it will be the same on 64 and 32
 bit systems (a 128 bit boundary, nice and fast for most modern
 cipher algorithms, sadly asking for it to match hash block
 sizes is a bit much).

  I don't have a horse in this race; but I am curious as to why
  you wouldn't ask for `chunkOverhead = 16' as that seems to be
  your intent as well as what the expression works out to on any
  machine in common use.

--
Jason Dusek
Linux User #510144 | http://counter.li.org/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Mining Twitter data in Haskell and Clojure

2010-07-04 Thread Jason Dusek
  So I wonder what the timings for Haskell, O'Caml and Clojure
  are now, given the patch to GHC.

--
Jason Dusek
Linux User #510144 | http://counter.li.org/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Good US Grad schools for functional languages?

2010-05-24 Thread Jason Dusek
2010/05/17 Tim Chevalier catamorph...@gmail.com:
 The first three names on that list of faculty members are members of
 the HASP group (High Assurance Systems Programming), which is an
 active research group focused on developing a call-by-value Haskell
 variant for systems programming. More info at
 http://hasp.cs.pdx.edu/

  Does call-by-value mean actually strict?

  Looking over the page on execution order on Wikipedia, it
  seems that there are degrees of strictness. I'm curious about
  the choice that was made with HASP. They seem to have bottom,
  according to the report; yet I don't know how you'd have
  bottom without laziness of some kind.

--
Jason Dusek
Linux User #510144 | http://counter.li.org/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Benchmarks game updated to ghc 6.12.2

2010-05-01 Thread Jason Dusek
2010/04/30 Don Stewart d...@galois.com:
 Prior to the upgrade we weren't mostly beaten on speed, so I think a bit
 of tuning (ghc -server :) should help.

  What do you mean by that? I tried searching the flags page:

http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/flag-reference.html

  I couldn't find a server flag.

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


Re: [Haskell-cafe] Lazy Parsing (ANN: vcd-0.1.4)

2010-04-27 Thread Jason Dusek
  So UU parsers can construct input? The presence of an
  empty list in the 2nd slot of the tuple is the only
  indicator of errors?

  For parsing datatypes without a sensible default value,
  what happens?

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


Re: [Haskell-cafe] Bulk Synchronous Parallel

2010-04-21 Thread Jason Dusek
2010/4/21 Aaron D. Ball aarondb...@gmail.com:
 I don't need a tool that automatically figures out how to distribute
 any workload in an intelligent way and handles all the communication
 for me.

  You are right in general. Only if you want to rely on purity and a
  few source code annotations to get you parallelism relatively
  cheaply do you care about these compiler approaches. This is something
  that Haskell can do that Ruby, C and friends really can not do -- thus
  I mention it.

 If I have the basic building block, which is the ability to
 serialize a Haskell expression with its dependencies and read them
 into another Haskell instance where I can evaluate them, I can handle
 the other pieces, which are

 - passing strings back and forth in whatever way is convenient
 - deciding how to divide up my workload.

  Do add also, configuring servers and their connections.

 In the Ruby universe, DRb combines the serialization and passing
 strings around job and lets me figure out how to divide up the work,
 and it would be delightful if there were something similarly simple in
 the Haskell world.

  I think Holumbus has got some promising stuff for user-managed
  distributed workers:

http://holumbus.fh-wedel.de/trac/browser/distribution

  What do you think?

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


Re: [Haskell-cafe] Bulk Synchronous Parallel

2010-04-20 Thread Jason Dusek
2010/04/19 Gregory Crosswhite gcr...@phys.washington.edu:
 Thanks for the link;  my ultimate interest, though, is in an architecture
 that could scale to multiple machines rather than multiple cores with shared
 memory on a single machine.  Has there been any interest and/or progress in
 making DPH run on multiple machines and other NUMA architectures?

  I wonder what it would take to do this.

  One approach is some compiler magic that provides you with an RTS
  that can communicate with other RTSen over TCP and chunks the computation
  appropriately. Or maybe you give it a chunk size and it gives you some
  number of executables that find one another using Bonjour. Values not on
  this node are found via some hashing scheme (the same scheme used to
  chunk in the first place).

  There is a lot to know about this problem area.

  It would be a great alternative to OpenMPI.

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


Re: Unicode alternative for '..' (ticket #3894)

2010-04-15 Thread Jason Dusek
  I think the baseline ellipsis makes much more sense; it's
  hard to see how the midline ellipsis was chosen.

--
Jason Dusek
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Type constrain in instance?

2010-04-09 Thread Jason Dusek
  You need to define the instance with `ChainableFunction' and
  not `CF' (the latter is value-level, not type level).

  Once you make that switch, you'll find yourself with an
  instance that is not compatible with the definition of the
  `Category' class.

Prelude Control.Category :info Category
class Category cat where
  id :: forall a. cat a a
  (.) :: forall b c a. cat b c - cat a b - cat a c
-- Defined in Control.Category

  We see that `id' and `.' have no class constraints and that
  there is in fact no where to place a class constraint on `a',
  `b' or `c'.

  I think that what you're looking for are restricted
  categories (and restricted monads and functors, as well,
  perhaps). A cursory search suggests the `data-category'
  package.

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


[Haskell-cafe] ANNOUNCE: JSONb-1.0.0

2010-04-07 Thread Jason Dusek
  A new release of JSONb, taking advantage of the latest Attoparsec.

http://hackage.haskell.org/package/JSONb-1.0.0

  Thanks to Grant Monroe for help with the numerics parser.

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


Re: [Haskell-cafe] ANNOUNCE: JSONb-1.0.0

2010-04-07 Thread Jason Dusek
2010/04/07 Ivan Lazar Miljenovic ivan.miljeno...@gmail.com:
 Jason Dusek jason.du...@gmail.com writes:
    A new release of JSONb, taking advantage of the latest Attoparsec.
 
      http://hackage.haskell.org/package/JSONb-1.0.0

 Is this meant to be a continuation of the json-b package?

  Yes. I moved to camel case because that is consistent with the
  module name.

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


Re: [Haskell-cafe] Hackage accounts and real names

2010-04-05 Thread Jason Dusek
2010/04/05 Casey McCann syntaxgli...@gmail.com:
 Not to mention that pseudonymity is overwhelmingly the norm on the
 internet.

  I suppose this is the collision of two cultures. Lambda the
  Ultimate also encourages (but does not require) real names. I
  think this has to do with academic values, really -- and the
  Haskell community has a lot of those. You don't submit papers
  under names like `solidsnack'.

  There certainly is a significant subculture of anonymity on
  the internet but maybe it has spread beyond its useful limits?
  There are places where it is helpful (Allberry's examples
  above come to mind) but I don't think contributing code to
  Hackage (or Cheeseshop or anything else) is like that.

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


Re: [Haskell-cafe] Time for a San Francisco Hackathon?

2010-04-03 Thread Jason Dusek
2010/04/03 Mark Lentczner ma...@glyphic.com:
 In particular, I think it would be cool to offer a Haskell
 teach-in.

  I think that'd be a cool event, yeah.

 Something like a half day, perhaps at one of the hacker
 locations...

  By hacker locations, I gather you mean Noisebridge or Hacker
  Dojo? If Noisebridge, I can help with that; I've been part of
  NB for some time.

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


Re: [Haskell-cafe] Apparently, Erlang does not have a static type system, since with hot code loading, this is intrinsically difficult.

2010-04-03 Thread Jason Dusek
2010/04/03 Casey Hawthorne cas...@istar.ca:
 Apparently, Erlang does not have a static type system, since with hot
 code loading, this is intrinsically difficult.

  It is doubtless hard to statically check a program that is
  not statically available :)

 If Haskell allows hot code loading, would this throw a wrench
 into the static type system?

  One can not gloss over the difference between statically
  verified and not; dynamic loading becomes essentially dynamic
  compiling and type-checking. You ship a statically checked
  Haskell program that is run to construct new Haskell programs.
  With `hint-server', for example, you have a statically checked
  master process which is shipped with the GHC inside and you
  load subprograms into their own environment; if type checking
  works then, hurray, it did and you run the subprogram. If not,
  well, you handle the error. The master process is static while
  the modules governed by it are not.

  I wonder, is it possible in Erlang to dynamically reload the
  entire runtime, stem-to-stern?

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


Re: [Haskell-cafe] Are there any female Haskellers?

2010-03-29 Thread Jason Dusek
2010/03/29 Alberto G. Corona agocor...@gmail.com:
 [...] What we evolved with is a general hability: to play with
 things to achieve what we need from them, (besides other
 abilities). The pleasure to acheve ends by using available
 means. [...]  A tool is someting used to solve a class of
 problems. It does not matter if it is something phisical or
 conceptual. [...] The more general is a tool, the more we feel
 pleasure playing with it

  So the adaptation you are saying men have in greater degree
  than women is pleasure in tool using, broadly defined to
  include taming animals, debate, programming, sword play,
  carpentry and more? What are you attributing to men is not
  so much superiority of ability but greater motivation?

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


Re: [Haskell-cafe] Are there any female Haskellers?

2010-03-29 Thread Jason Dusek
2010/03/29 Jason Dusek jason.du...@gmail.com:
 What are you attributing to men...

   s/are you/you are/

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


Re: [Haskell-cafe] Re: Are there any female Haskellers?

2010-03-28 Thread Jason Dusek
Am 28. März 2010 07:15 schrieb Jan-Willem Maessen jmaes...@alum.mit.edu:
 A relatively recent article in CACM made much the same point for CS;
 particularly noteworthy to me is the rather different proportion of
 undergrad CS majors in different countries (the US is particularly low):
 http://portal.acm.org/citation.cfm?id=1461928.1461947coll=portaldl=ACMidx=J79part=magazineWantType=Magazinestitle=Communications

  I believe this is the same article, available free of charge:

http://www.cs.umass.edu/~lfriedl/tmp/cacm-2009-02-womenInCS.pdf

  The relative rates of graduation are on the first and second
  pages.

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


Re: [Haskell-cafe] Re: Haskell-friendly Linux Distribution

2010-03-28 Thread Jason Dusek
2010/03/28 Ertugrul Soeylemez e...@ertes.de
 However, as always there is a catch.  Gentoo is a source distribution,
 which means that you compile the entire system from scratch.  On modern
 computers this is quite fast, but sometimes it can hammer on your
 patience.

  To be fair, Gentoo has a well thought out system for bundling up
  an installed build and creating a binary package for installation
  on other nodes.

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


Re: [Haskell-cafe] Re: Are there any gay haskelleres?

2010-03-28 Thread Jason Dusek
  I am replying off list. I hope others will do the same.

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


Re: [Haskell-cafe] Are there any female Haskellers?

2010-03-27 Thread Jason Dusek
2010/03/27 Alberto G. Corona agocor...@gmail.com:
 To say this in scientific headline jargon, it's a matter of
 division of work, time, and dimorphic fixation of abilities in
 the brain by natural selection trough dimorphic development of
 the brain of men and women by different genetic sequences. I
 don't know any kind of tool more flexible and powerful than a
 computer language. Men are good at making tools and using
 them. They invested more in engineering because this activity
 were more critical for their success than in the case of
 women. Sociological or cultural explanations don't explain the
 universal tendencies and habilities across cultures and time.

  In this passage, you seem to attribute to men a relatively
  great adaptation for making  using tools, relative to women.
  You suggest this applies to computer languages -- excellent
  tools -- and this explains the relative absence of women in
  computing.

  It's hard to take your remarks seriously; consider:

 .  There is no single adaptation for tool using. Men differ
greatly in their aptitude for working with different kinds
of tools.

 .  The relevance of tools in women's lives is well known; there
are few cultures that have not allocated some essential
domain of work -- fabric arts, tanning, cooking, picking
certain plants -- to women. It's hard to see any support for
the notion that tools are more (or less) critical for the
evolutionary success of men.

  Though this may be your honest theory, you don't offer much
  support for it. When offering a theory as to the relative
  success of one movie over another, I suppose there is not a
  great burden of proof; but carelessness in the matter of which
  kind of person can do which kind of work has hurt too many
  people for too long.

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


Re: [Haskell-cafe] Are there any female Haskellers?

2010-03-27 Thread Jason Dusek
2010/03/27 Leon Smith leon.p.sm...@gmail.com:
 I've heard rumors that in the early days of programming, that
 women were in the majority, or at least they represented a
 much greater proportion of programmers than they do now. I
 seem to recall that this started to change sometime in the
 60s. Of course, I can't recall when or where I heard these
 stories, and I'm not sure that my source was reliable, so I
 might be completely off on this count.

  Women have been computers for a long time but they were not
  generally the majority or even very well represented.

http://www.thenewatlantis.com/publications/the-age-of-female-computers

  In the Second World War, however, this changed; many, many
  women were brought into the computer corps and the first six
  programmers of the ENIAC, all women, were drawn from that
  corps.

http://en.wikipedia.org/wiki/Human_computer

  So it may have happened that women started out as the majority
  of programmers and maintained that role for awhile; but as
  computing evolved more men came to desire the position. Of
  course, all the bosses were still men; they might prefer to
  hire other men. Coupled with conservative attitudes about
  women at work, programming would've become more and more
  hostile for women and maybe they were motivated to leave.

  A friend of mine, an engineer now in San Francisco, used to
  work in defense in Australia. The defense industry there is
  apparently as conservative as it is in the United States.
  There were alot of people around who felt that women needn't
  be in the work place or have jobs like mechatronic engineer.
  She was greatly motivated to leave. In the forties, where
  would she have gone?

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


Re: [Haskell-cafe] compiler management for Haskell a la RVM?

2010-03-17 Thread Jason Dusek
2010/03/16 Brandon S. Allbery KF8NH allb...@ece.cmu.edu:
 On Mar 16, 2010, at 20:59 , Mark Wotton wrote:
  Do we have any similar system for ghc/cabal? I quite
  frequently find myself switching between 6.10 and 6.12 for
  various things, and it's always a bit painful to get your
  environment up to speed. Is there a golden road for this
  stuff, or do the compiler hackers here just munge the PATH?

 Both the system and user package databases handle multiple
 compiler versions, and Cabal inherits this so should do the
 right thing for the most part.

 The GHC environment I've assembled for campus machines
 installs versioned commands (including adding versions to the
 commands that lack them), then a script uses the machine
 configuration db to install symlinks for the default version.

  While I've not worked with it much, Nix seems like a complete,
  well-thought system for building out multi-versioned package
  installations. Have you looked at it? What do you think?

  Finding myself in a similar situation, I wonder if it's not
  ultimately better to leverage the work of the Nix team,
  instead of building a simpler system for Haskell (and then
  later for Ruby and then...).

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


Re: [Haskell-cafe] Real-time garbage collection for Haskell

2010-03-02 Thread Jason Dusek
2010/02/28 Neil Davies semanticphilosop...@googlemail.com:
 I've never observed ones that size. I have an application that runs in 'rate
 equivalent real-time' (i.e. there may be some jitter in the exact time of
 events but it does not accumulate). It does have some visibility of likely
 time of future events and uses that to perform some speculative garbage
 collection.

  Do you have information on how it behaves without speculative
  GC?

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


Re: [Haskell-cafe] do we need types?

2010-02-26 Thread Jason Dusek
  This reminds me of an email posted to this list long ago
  by Luke Palmer, describing a use of records-as-interfaces
  in Agda.

--
Jason Dusek


-- Forwarded message --
From: Luke Palmer lrpal...@gmail.com
Date: 2009/12/29
Subject: Re: [Haskell-cafe] Alternatives to type classes.
To: Jason Dusek jason.du...@gmail.com
Cc: haskell haskell-cafe@haskell.org


On Tue, Dec 29, 2009 at 6:22 PM, Jason Dusek jason.du...@gmail.com wrote:
  Consider the real numbers. They are a group. We have an
  identity element `0', inverses and closure under the associative
  operation `+'.

Group+ = (+, 0, -1 * _)

  They are another group, too -- the group with `*':

Group* = (*, 1, 1 / _)

Ignoring 0 for sake of discussion.

  This seems like a real problem with the whole notion of
  typeclasses -- we can't really say a set/type is its
  extension with some new operations.

  One road to go on this is to make every extension of the set
  with new ops a different type; but that seems really horribly
  inconvenient. I wonder what approaches have been tried here?

I consider typeclasses a happy notational medium.  They are not
perfect, they miss some cases, but they are pretty good.

For full generality at the expense of some verbosity, I like Agda's
solution pretty well.  Agda allows you to open a record into a
scope.

record Group (a : Set) where
 field
   _+_ : a - a - a
   -_ : a - a
   0 : a

conj : {a : Set} - Group a - a - a - a
conj g x y = x + y + (-x)
   where open g

Maybe I even got the syntax right :-P

The cool thing is that you can use this for the invariant-keeping
property of typeclasses, too.  Eg. Data.Map relies on the fact that
there is at most one Ord instance per type.  By parameterizing the
module over the Ord record, we can do the same:

record Ord (a : Set) where ...

module MapMod (a : Set) (ord : Ord a) where
 Map : b - Set
 Map = ...
 insert : {b : Set} - a - b - Map b - Map b
 insert = ...
 ...

So we have the liberty of being able to use different Ord instances,
but different Ord instances give rise to different Map types, so we
can not violate any invariants.

You can do something similar in Haskell using an existential type,
although it is very inconvenient:

data Ord a = ...
data MapMod map a b = MapMod { empty :: map a b, insert :: a - b -
map a b - map a b, ... }

withMap :: Ord a - (forall map. MapMod map a b - z) - z
withMap ord f = f ( {- implement MapMod here, using ord for ordering }- )

Then you could use maps on different Ords for the same type, but they
could not talk to each other.

Some syntax sugar could help the Haskell situation quite a lot.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] hmake and hat

2010-02-25 Thread Jason Dusek
  Can you provide a link to something describing the error?

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


Re: [Haskell-cafe] Re: How many Haskell Engineer I/II/IIIs are there?

2010-02-15 Thread Jason Dusek
2010/02/15 Tom Tobin korp...@korpios.com:
 On Mon, Feb 15, 2010 at 2:24 AM, Michael Lesniak mlesn...@uni-kassel.de 
 wrote:
   There's the subReddit: http://www.reddit.com/r/haskell_proposals/
 
  I know it. The problem is that (at least in my opinion) only a small
  fraction of Haskell'ers use it.

 I strongly dislike social X sites (where X is networking,
 bookmarking, etc.).  I'd rather keep that sort of thing on mailing
 lists, wikis, and bug trackers.

  A Haskell proposals mailing list would work well, I
  think. I didn't have the necessary permissions to
  create mailing lists for haskell.org, though.

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


[Haskell-cafe] Two authors especially likely to be spammed.

2010-02-15 Thread Jason Dusek
  I recently discovered that many haskell-cafe mails are
  being dumped in my SPAM folder. A lot of them are from John
  Lato and Simon Marlow.

  I wonder if anyone else has experienced this?

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


Re: [Haskell-cafe] Time for a San Francisco Hackathon?

2010-02-12 Thread Jason Dusek
  I'd help organize. How do these usually work? Some worthy package
  is selected for hacking? People hack whatever they like?

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


Re: [Haskell-cafe] Re: How many Haskell Engineer I/II/IIIs are there?

2010-02-12 Thread Jason Dusek
2010/02/12 stefan kersten s...@k-hornz.de:
 On 12.02.10 16:29, Simon Marlow wrote:
  I'm aware that some people need a GC with shorter pause
  times.  We'll probably put that on the roadmap at some point.

 for some applications (like realtime audio processing) it
 would be interesting to even have short pause times with a
 guaranteed upper bound, but i realize this is a very
 specialized need that could be better served by making the GC
 implementation swappable (which otoh doesn't seem to be
 trivial).

  I think this is not a unique need. When you consider things
  like scalable network services with strong SLAs, largish
  embedded systems (iPhone, planes, c.) and other environments
  where verification is a big win, it's generally also important
  to control latency and memory use.

  To be honest, though, I am of two minds about this. Why
  shouldn't we enforce our timing/memory requirements by writing
  EDSLs and compiling them? The approach Atom takes is maybe the
  most flexible option (there be parens, though).

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


Re: [Haskell-cafe] Re: How many Haskell Engineer I/II/IIIs are there?

2010-02-11 Thread Jason Dusek
  Is JHC not suitable in this case? It won't compile all of
  Haskell but it does some to be doing the right things as
  regards a pluggable RTS.

  I think it's fair to say at this point that GHC can compile
  all the Haskell we want and that new Haskell pieces will come
  to GHC before anything else gets them. So going with a totally
  new system, front-to-back, is not really desirable when all
  you want is a new RTS; however, I don't think GHC was designed
  to be a Haskell compiler superserver.

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


Re: [Haskell-cafe] Re: How many Haskell Engineer I/II/IIIs are there?

2010-02-11 Thread Jason Dusek
  Things are missing but Haskell was certainly fit for
  practical use two years ago.

  The big things missing now are trust, mindshare and
  enough people who think reliability and consistency
  are a good play for long term productivity.

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


Re: [Haskell-cafe] Re: How many Haskell Engineer I/II/IIIs are there?

2010-02-11 Thread Jason Dusek
  I looked at generating C for AVR with JHC. I wanted to see what
  this program became:


http://github.com/solidsnack/trippy-waves/blob/99ad424a3ed4a21ff6f6a662293d6d21e92d6611/using-jhc/RGB.hs

  The program is relatively simple. It doesn't work, of course (I
  never did get the right FFI bindings figured out) but the
  generated C is suggestive.


http://github.com/solidsnack/trippy-waves/blob/99ad424a3ed4a21ff6f6a662293d6d21e92d6611/using-jhc/hs.out_code.c

  The generated `main' is very plain:

static void A_STD
ftheMain(void)
{
jhc_function_inc();
uintptr_t v10 = ((uintptr_t)DDRB());
*((uint8_t *)(v10)) = 23;
uintptr_t v18 = ((uintptr_t)PORTB());
return *((uint8_t *)(v18)) = 23;
}

  This is a simple, literal translation of my foreign calls. To
  all appearances, the runtime is entirely bypassed. The
  function `jhc_function_inc()' is a performance counter, set to
  no-op for non-profiling builds as far as I can tell.

  It also doesn't compile but that's because I can't figure out
  how to declare pointers in the FFI; and if I could, then I'd
  have to go through by hand and pull out includes for things
  that aren't available for AVR programming -- locale.h and
  such.

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


[Haskell-cafe] How many Haskell Engineer I/II/IIIs are there?

2010-02-10 Thread Jason Dusek
  Although I'm fond of Haskell, in practice I am not a
  Haskell programmer -- I'm paid for Ruby and Bourne shell
  programming.

  Many of the jobs posted on this list end up being jobs
  for people who appreciate Haskell but will work in C# or
  O'Caml or some-such.

  I wonder how many people actually write Haskell,
  principally or exclusively, at work?

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


Re: [Haskell-cafe] How many Haskell Engineer I/II/IIIs are there?

2010-02-10 Thread Jason Dusek
2010/02/10 Tom Tobin korp...@korpios.com:
 On Wed, Feb 10, 2010 at 9:59 AM, Jason Dusek jason.du...@gmail.com wrote:
  I wonder how many people actually write Haskell,
  principally or exclusively, at work?

 While I don't suspect the number is large at the moment, the
 same thing could have been said several years ago of the
 language I use at my current job and used at my last job:
 Python.  I get the same industrial incubation period vibe
 (for lack of a better term) from Haskell that I once got from
 Python -- although perhaps I'm biased in that I simply *like*
 these languages, too.  :p

  I completely agree. I'm just trying to figure out where on the
  growth curve we are :) I am also interested in what industries
  tend to aggregate Haskell programmers. Within the Bay Area
  webosphere, Haskell is not much liked though Scala is gaining
  some traction. I think this has a lot to do with the fact that
  web programming is very much a let's go shopping kind of
  discipline -- no point in troubling oneself over correctness
  when the users haven't weighed in on the worth of your site.
  Of course this attitude leads to a long maintenance phase of
  Crazy Stuff®, like writing a PHP compiler; but by then you
  have piles of money to throw at the problem! Such is the
  theory, anyways.

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


Re: [Haskell-cafe] How many Haskell Engineer I/II/IIIs are there?

2010-02-10 Thread Jason Dusek
2010/02/10 Roderick Ford develo...@live.com:
 A U.S. president would probably subsidize such a job-creating endeavor too!

  The US government generally subsidizes these kinds of things
  through DoD spending (and a few NSF grants). That is probably
  hard to get into.

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


Re: [Haskell-cafe] Using Cabal during development

2010-02-09 Thread Jason Dusek
  My development environment is a Screen with Bash, Vim and GHCi
  running.

  If I can just load the files in GHCi or compile them with GHC
  without specifying many options or extensions, then I just do
  it that way. As soon as I feel a need to write a Makefile or a
  little build script, I write a Cabal file instead and switch
  to using `cabal-install'.

  When I say many options or extensions, I nearly mean any.
  Most projects of mine get a Cabal file at the point where I
  feel the need for the first `LANGUAGE' pragma. (I usually omit
  `LANGUAGE' pragmas, delegating to Cabal for that. I'm not sure
  whether this is good or bad practice.)

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


Re: Quasi quoting

2010-02-01 Thread Jason Dusek
2010/02/01 Simon Peyton-Jones simo...@microsoft.com:
 That might be quite convenient, but alas [|...|] has already
 been taken by Template Haskell quotes, meaning [e| ...|].  So
 you'd need something else.  [*|...|]  perhaps.

  Why is that a problem? Would TH and quasi-quoting be likely to
  be enabled at the same time? One could decide in favour of QQs
  if they are enabled (though yes, this is likely horrible on
  the inside).


 Or we could switch to different quotation brackets altogether
 for quasiquotation, the obvious possibility being
 |...blah...|, and pads|...blah...|. [...]

  It's true; but I suspect `|' and `|' are actually widely
  used. Wouldn't `(|' and `|)' be safer?

  In either case, it's easy to see how me evolve an
  indentational quasi-quote syntax: `[|]' or `(|)'. If the
  default quasi-quoter is simple string literals, then there's
  no need for a HEREDOC in the language.

--
Jason Dusek
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


  1   2   3   4   5   >