Re: [Haskell-cafe] indentation with let and do

2013-10-03 Thread Brandon Allbery
On Thu, Oct 3, 2013 at 2:31 PM, Corentin Dupont
wrote:

> test :: Bool -> IO ()
> test foo = do
>let bar = case foo of
>True ->  "Foo";
>False -> "Bar"
>return ()
>
> while this one does (just adding one space in front of True and False):
>
> test :: Bool -> IO ()
> test foo = do
>let bar = case foo of
> True ->  "Foo";
> False -> "Bar"
>return ()
>

Do you understand how layout works? Informally, something that is more
indented is a continuation of the previous expression, while something
equally or less indented is a new expression. In this case, the previous
expression is `bar = case foo of` and indenting `True` to the same level as
`bar` means you have ended the expression starting with `bar =`. Adding
just one extra space indicates that it's still part of `bar =`.

(ghc is actually being somewhat lenient here; strictly speaking, you are
not indented beyond the `case` so it should have ended the `case`
expression. ghc allows some sloppiness like this when there absolutely must
be something else after, but there are limits mostly imposed by layout
introducers like `let` and `do`.)

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


Re: [Haskell-cafe] Strange exit status behavior from the process package

2013-09-21 Thread Brandon Allbery
On Sat, Sep 21, 2013 at 11:12 PM, Michael Xavier
wrote:

> I've run into some strangeness with the process package. When you kill
> some processes on the command line you correctly get a non-zero exit
> status. However when using the process package's terminateProcess (which
> sends a SIGTERM), it returns an ExitSuccess:
>

The 143 you get from the shell is synthetic (and nonportable). Signals are
not normal exit codes; WEXITSTATUS is not defined in this case (but often
will be 0, as seems to be shown here), instead WTERMSIG will be set to the
signal that terminated the process. The caller should be using WIFEXITED /
WIFSIGNALED / WIFSTOPPED to determine the cause of the termination and then
the appropriate WEXITSTATUS / WTERMSIG / WSTOPSIG call to determine the
value.

It sounds like the createProcess API does not recognize signal exit at all,
and uses WEXITSTATUS even when it is not valid.

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


Re: [Haskell-cafe] Mystery of an Eq instance

2013-09-21 Thread Brandon Allbery
On Sat, Sep 21, 2013 at 12:43 PM, David Thomas wrote:

> Sure.  An interesting, if not terribly relevant, fact is that there are
> more irrational numbers that we *can't* represent the above way than that
> we can (IIRC).
>

I think that kinda follows from diagonalization... it does handle more
cases than only using rationals, but pretty much by the Cantor diagonal
argument there's an infinite (indeed uncountably) number of reals that
cannot be captured by any such trick.

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


Re: [Haskell-cafe] Mystery of an Eq instance

2013-09-21 Thread Brandon Allbery
On Sat, Sep 21, 2013 at 12:35 PM, Bardur Arantsson wrote:

> On 2013-09-20 18:31, Brandon Allbery wrote:
> [--snip--]
> > unless you have a very clever representation that can store
> > in terms of some operation like sin(x) or ln(x).)
>
> I may just be hallucinating, but I think this is called "describable
> numbers", i.e. numbers which can described by some (finite) formula.
>
> Not sure how useful they would be in practice, though :).
>

I was actually reaching toward a more symbolic representation, like what
Mathematica uses.

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


Re: [Haskell-cafe] Mystery of an Eq instance

2013-09-20 Thread Brandon Allbery
On Fri, Sep 20, 2013 at 12:17 PM, damodar kulkarni
wrote:

> Ok, let's say it is the effect of truncation. But then how do you explain
> this?
>
> Prelude> sqrt 10.0 == 3.1622776601683795
> True
> Prelude> sqrt 10.0 == 3.1622776601683796
> True
>

Because there's no reliable difference there. The truncation is in bits
(machine's binary representation) NOT decimal digits. A difference of 1 in
the final digit is probably within a bit that gets truncated.

I suggest you study IEEE floating point a bit. Also, study why computers do
not generally store anything like full precision for real numbers. (Hint:
you *cannot* store random real numbers in finite space. Only rationals are
guaranteed to be storable in their full precision; irrationals require
infinite space, unless you have a very clever representation that can store
in terms of some operation like sin(x) or ln(x).)

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


Re: [Haskell-cafe] Trouble installing haskeline: ExitFailure 139

2013-09-14 Thread Brandon Allbery
On Sat, Sep 14, 2013 at 4:57 PM, David Banas  wrote:

> Has anyone else hit an unexplained *ExitFailure 139* when trying to
> install the *haskeline* package?
>

139 sounds like how the shell passes on "Segmentation fault (core dumped)".

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


Re: [Haskell-cafe] Proposal: New syntax for Haskell

2013-09-12 Thread Brandon Allbery
On Thu, Sep 12, 2013 at 6:00 PM, David Thomas wrote:

> I've long been interested in a scripting language designed to be spoken.
> Not interested enough to go about making it happen... but the idea is
> fascinating and possibly useful.
>

http://en.wikipedia.org/wiki/Shakespeare_(programming_language) ?   :)

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


Re: [Haskell-cafe] Unary functions and infix notation

2013-09-06 Thread Brandon Allbery
On Fri, Sep 6, 2013 at 11:04 AM, Johannes Emerich wrote:

> Desugaring of an equivalent source file shows that id is applied to the
> anonymous function, which is then applied to 1.
>
> The following example of a function that is not polymorphic in its return
> type behaves closer to what I would have expected: It does not work.
>
>Prelude> let z = (\y -> True) :: a -> Bool
>Prelude> :t (`z` True)
>
>:1:2:
>The operator `z' takes two arguments,
>but its type `a0 -> Bool' has only one
>In the expression: (`z` True)
>
> What is the purpose/reason for this behaviour?
>

Coming from another language, where functions aren't first class, you will
probably be used to the notion that a function type is somehow different
from any other type. You'll need to unlearn that for functional languages:
function types are just as "real" as (Integer) is, and if I have a type
variable somewhere which doesn't have constraints otherwise preventing it,
that type variable can end up being (Integer) or (a -> a) or (Num c => c ->
c -> c) or (Maybe [x]) or (Maybe (a -> a)) or any other (rank-1, i.e. no
internal "forall"s) type.

(id) has the type (a -> a); in the use mentioned in the first quoted
paragraph, this has unified (a) with (b -> b) to produce (id :: (b -> b) ->
(b -> b)) in order for the whole expression to be typeable. In your second
example, you don't have polymorphism "where it's needed" so it can't infer
a type that will work.

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


Re: [Haskell-cafe] How to read a file and return a String?

2013-09-04 Thread Brandon Allbery
On Wed, Sep 4, 2013 at 10:21 AM, yi lu wrote:

> I want to read a text file, and store it in a *String*. But readFile will
> get *IO String*. I search with google and they tell me it is not
> necessarily to do so. Can you explain to me why is this? Furthermore, How
> to read a file and store it in a String?
>

You do not do so directly. An IO action is a promise to produce a value,
not an actual value. (readFile contains a String in the same way the "ls"
or "dir" command contains a list of files.)

I suggest you take a look at
http://learnyouahaskell.com/input-and-output#files-and-streams to see how
IO works in Haskell.

tl;dr: use do notation (which lets you pretend to a limited extent that you
can see the String in an IO String) or >>= or fmap to attach a callback to
the IO "promise".

readFile >>= (something that operates on a String and produces an IO
whatever)

do s <- readFile
   (something that operates on a String and produces an IO whatever)

Note that in the end it's still in IO. You can't escape it. (There are
actually ways to "escape" but they will get you into trouble fairly quickly
because they don't work the way you want them to.)

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


Re: [Haskell-cafe] Unexpected behaviour with send and send-buffer setting

2013-09-03 Thread Brandon Allbery
On Tue, Sep 3, 2013 at 7:58 PM, Joey Adams wrote:

> On Tue, Sep 3, 2013 at 6:56 PM, Simon Yarde  wrote:
>
>> I'm new to Haskell and have reached an impasse in understanding the
>> behaviour of sockets.
>>
>> The crux of my line of enquiry is this;  how can my application know when
>> to pause in generating its chunked output if send doesn't block and the
>> current non-blocking send behaviour apparently succeeds when the send
>> buffer should be full?
>>
>
> 'send' will eventually block after enough 'send's without matching
> 'recv's.  As Brandon explains, there is more buffering going on than the
> send buffer.  In particular, the receiving host will accept segments until
> its buffer fills up.  TCP implements flow control (i.e. keeps the sender
> from flooding the receiver) by
>

Also note that, if you're using TCP, Nagle's algorithm will be turned on
unless you specifically turn it off; this is explicitly designed to avoid
sending very short packets, by buffering them into larger packets in the
kernel network stack up until some timeout or a minimum threshold size is
reached. (Protocols such as ssh and telnet turn it off for interactivity.)
And if you're using UDP, there's no flow control at all; while packets
won't be aggregated á la Nagle, the network stacks on the sending and
receiving ends can do pretty much whatever they want with the individual
packets. And in either case the socket buffer size is only the "last mile":
there is no way to control what happens elsewhere, and in particular the
interrupt-time received packet handling usually won't know even what socket
is the target, much less what buffer size that socket has set.

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


Re: [Haskell-cafe] World's First Commercial Haskell IDE and Deployment Platform, FP Haskell Center Launches Today

2013-09-03 Thread Brandon Allbery
On Tue, Sep 3, 2013 at 3:35 PM, Mathijs Kwik wrote:

> You can always try the attached docx! :)


Which likewise showed nothing.

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


Re: [Haskell-cafe] Unexpected behaviour with send and send-buffer setting

2013-09-03 Thread Brandon Allbery
On Tue, Sep 3, 2013 at 6:56 PM, Simon Yarde  wrote:

> I've found that setting the send buffer size causes send to truncate the
> ByteString to the buffer size, but that successive sends continue to
> succeed when the buffer should be full.
>

I see no actual flow control here. That the receiver is blocked does not
mean the receiver's *kernel* has not received the packets and buffered
them. Also note that send is not synchronous; it cannot know that the
receiver has hit its buffer limit --- and the kernel may well have already
sent the previous packet, so the send buffer is in fact empty at that
point, with the pending packet either in flight or in the receiving
kernel's (interrupt time or normal; they are usually distinct. Or, with a
sufficiently fancy network card, its own) network buffers.

In short, you have not thought through all the possible ramifications, nor
considered that the kernel handles packets and buffering independently of
your program, nor considered the effects of the non-instantaneous network
between sender and receiver. It may or not behave differently when sender
and receiver are on the same machine. Do not assume that the kernel will
short-circuit here and leave out all the intermediate buffering! The only
part you're guaranteed to avoid is the interface with the network hardware.

The crux of my line of enquiry is this;  how can my application know when
> to pause in generating its chunked output if send doesn't block and the
> current non-blocking send behaviour apparently succeeds when the send
> buffer should be full?
>

I would suggest reading a book on TCP/IP networking.

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


Re: [Haskell-cafe] Template Haskell: let statement in a splice put in the "main = do" part of a program?

2013-08-24 Thread Brandon Allbery
On Sat, Aug 24, 2013 at 11:00 AM, TP  wrote:

> main = do
>
> $(makeLetStatement "a")
> -- print a
>

Is that the actual indentation you used? Because it's wrong if so, and the
error you would get is the one you're reporting. Indentation matters in
Haskell.

In an equation for `main': main = do { $(makeLetStatement "a") }
>

You cannot *end* a do with a let-statement; it requires something else
following it. You have nothing following it, as shown by the above fragment
from the error message.

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


Re: [Haskell-cafe] Errors in non-monadic code

2013-08-19 Thread Brandon Allbery
On Mon, Aug 19, 2013 at 2:59 PM,  wrote:

> I'd say that if you were in the context of the IO monad, maybe you'd
> prefer to use exceptions instead of 'Either' or 'Maybe'.
>

Even in IO, exceptions should be reserved for truly exceptional conditions
(of the "program cannot safely continue" variety), not merely for error
checking when this can be described as a normal flow of evaluation.
Exceptions are not simply alternative flow of control, even in procedural
languages; they are *disruptions* of flow of control.

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


Re: [Haskell-cafe] Errors in non-monadic code

2013-08-19 Thread Brandon Allbery
On Mon, Aug 19, 2013 at 2:09 PM, Brandon Allbery wrote:

> Alternatively, have you considered using your own ADT? `data Validity =
> Success | Failure String` would give you more readable / comprehensible
> code without needing to worry about assumptions or common usage.


Or possibly Valid and Invalid as the constructors

This also means you can easily extend it later to include multiple errors,
or position information, or other annotations. You could also use it with
Monoid and/or the Writer monad to track success/failure in the most
appropriate way for your project, instead of being constrained to the
behavior of an existing instance.

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


Re: [Haskell-cafe] Errors in non-monadic code

2013-08-19 Thread Brandon Allbery
On Mon, Aug 19, 2013 at 1:48 PM,  wrote:

> What is the proper way to implement a non-monadic function that checks
> whether a given value is correct and gives a proper error message
> otherwise ? What is the recommended option ?
>
> * Either String a
>

Preferred, usually, since Nothing is regarded as an error condition of
sorts: the Monad instance for Maybe associates Nothing with `fail`, which
is invoked on failed pattern matches; likewise it's mzero for MonadPlus and
mempty for Monoid, both of which use it (differently) to reflect certain
"failure" scenarios).

If nothing else, it would be highly confusing to see Nothing associated
with success given its widespread association with failure.

Alternatively, have you considered using your own ADT? `data Validity =
Success | Failure String` would give you more readable / comprehensible
code without needing to worry about assumptions or common usage.

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


Re: [Haskell-cafe] abs minBound < (0 :: Int) && negate minBound == (minBound :: Int)

2013-08-19 Thread Brandon Allbery
On Mon, Aug 19, 2013 at 11:43 AM, Kyle Miller  wrote:

> Or, three other options: 1) make MIN_INT outside the domain of abs, 2)
> make the range of abs be some unsigned int type, or 3) use Integer (i.e.,
> use a type which actually represents integers rather than a type which can
> only handle small integers).
>

I think I would just document that Int is intended to represent a machine
word and therefore inherits the behavior of machine words, behavior at its
extrema is subject to the CPU behavior as a result, and if consistent
behavior is required then Integer should be used. (Indeed, it should
probably note that Int is a performance hack; but then you run into all the
Data.List etc. functions that use it.)

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


Re: [Haskell-cafe] Database.postgreSQL.Simple - ambigious type

2013-08-17 Thread Brandon Allbery
On Sat, Aug 17, 2013 at 5:59 PM, Hartmut Pfarr
wrote:

>   query_ conn "select 2 + 2"
>
> I've no errors any more.
> But: I don't see any result (for sure, it is not coeded yet)
>

Yes, because you're not capturing it; it's the return value from `query_`,
which you are throwing away above instead of capturing with some kind of
`res <- query_ ...`. Again, see that section of the documentation I pointed
to for how to get results.

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


Re: [Haskell-cafe] Database.postgreSQL.Simple - ambigious type

2013-08-17 Thread Brandon Allbery
On Sat, Aug 17, 2013 at 1:35 PM, Hartmut Pfarr
wrote:

> (The example is identical to the first 5-liner-example in the package
> documentation)
>

As I read it, the example has a typo: it should be using `query_` instead
of `query`. See
http://hackage.haskell.org/packages/archive/postgresql-simple/0.3.5.0/doc/html/Database-PostgreSQL-Simple.html#g:9for
detals.

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


Re: [Haskell-cafe] Applicative is like an Arrow

2013-08-16 Thread Brandon Allbery
On Fri, Aug 16, 2013 at 10:49 AM, Tom Ellis <
tom-lists-haskell-cafe-2...@jaguarpaw.co.uk> wrote:

> On Fri, Aug 16, 2013 at 10:26:42AM -0400, Brandon Allbery wrote:
> > My understanding is that there's a rework of Arrow in progress that may
> > change this in the future, since *theoretical* Arrows are more distinct,
> > flexible and useful than the current implementation.
>
> I'd like to know more about that if you can provide any references.  I am
> using
> arrows very heavily.
>

It's been mentioned (but not much more) in #haskell IRC, so I don't know
details. I also expect it's not going to simply replace the current one, at
least not initially; and I think it's supposed to maintain compatibility
with the current Arrow because that's just a specialization to the function
arrow.

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


Re: [Haskell-cafe] Applicative is like an Arrow

2013-08-16 Thread Brandon Allbery
On Fri, Aug 16, 2013 at 10:04 AM, Thiago Negri  wrote:

> I just stumbled upon the Applicative term.
> Arrows are quite difficult for me to understand at the moment.
> I guess it needs time to digest.
>
> But, as I understand so far, Applicative and Arrows looks like the same
> thing.
>

Practically, that's not too far off. Arrows, at least as implemented
currently, have a number of significant restrictions based on the need for
the `arr` combinator to accomplish much of anything; Applicative has, as a
result, largely taken over the spot in the Haskell ecosystem that Arrow was
originally intended to fill.

My understanding is that there's a rework of Arrow in progress that may
change this in the future, since *theoretical* Arrows are more distinct,
flexible and useful than the current implementation.

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


Re: [Haskell-cafe] more gtk help

2013-08-13 Thread Brandon Allbery
On Tue, Aug 13, 2013 at 10:45 PM,  wrote:

> fooBar =
> do putStrLn "foo"
>return True
>
> so then I thought, aha!, all I need to do is understand the type of
> "return True" and all will be revealed to me.  Well, it's this:
>
>  Control.Monad.Trans.Reader.ReaderT
>(GHC.Ptr.Ptr Gtk.EExpose) IO Bool
>
> just like the error message says.
>
> Still don't know what that's supposed to be.  I'm having trouble tracking
> down
>
> Control.Monad.Trans.Reader.ReaderT
>

In this case, all you need to know is the Control.Monad.Trans part and the
IO underneath; this tells you that you can use `lift` and possibly `liftIO`
to get at the IO.

fooBar = do
liftIO $ putStrLn "foo"
return True

If `liftIO` complains about a missing MonadIO instance, file a bug :) but
you can also get there by using `lift` to reach it; in this case you only
need it once, but for more deeply nested transformers you may need it
multiple times (e.g. `lift . lift . lift $ putStrLn "foo"` for a stack of 3
transformers over IO).

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


Re: [Haskell-cafe] llvm on macos

2013-08-10 Thread Brandon Allbery
On Sat, Aug 10, 2013 at 12:53 PM, Dominic Steinitz wrote:

> Thank you very much. I used Homebrew. Now I can compile albeit with a
> warning. I have yet to try running it.
>
> Loading package repa-3.2.3.1 ... linking ... done.
> You are using a new version of LLVM that hasn't been tested yet!
> We will try though...
>
> There may be some support for requesting specific versions from Homebrew.
With MacPorts I can install any or all of LLVM 2.9 through 3.4 (prerelease)
and then use port select to specify which one is default (or even make
Apple's the default while keeping the MP ones available).

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


Re: [Haskell-cafe] Renumbered mailing list posts

2013-08-10 Thread Brandon Allbery
On Sat, Aug 10, 2013 at 11:38 AM, Niklas Hambüchen  wrote:

> (Also fact that hpaste just went away, invalidating all my links to
> hpastes, is similarly bad.)


Those at least are recoverable, just replace hpaste.org with
lpaste.net(content is still there). But still.

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


Re: [Haskell-cafe] llvm on macos

2013-08-10 Thread Brandon Allbery
On Sat, Aug 10, 2013 at 7:39 AM, Dominic Steinitz wrote:

> :
> Warning: Couldn't figure out LLVM version!
>  Make sure you have installed LLVM
> ghc: could not execute: opt
>
> The ghc documentation
> (
> http://www.haskell.org/ghc/docs/7.6.1/html/users_guide/code-generators.html
> )
> says that llvm and clang are installed by default for 10.6 and
> later. I am on 10.8.3.
>

Apple *still* doesn't ship a full LLVM for some reason. I installed one via
MacPorts; Homebrew also has it. Maybe if enough people file bugs with
Apple, they'll start providing the whole thing instead of just the parts
they use in Xcode. :/

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


Re: [Haskell-cafe] Installing wxHaskel on Snow Leopard

2013-08-08 Thread Brandon Allbery
On Thu, Aug 8, 2013 at 12:04 PM, Eduardo Sato wrote:

> Would it be necessary to change Info.plist?
>

I don't believe so; Info.plist is the externally visible interface details,
but these libraries should be hidden inside the app bundle and not visible
outside of it. When the runtime dynamic library loader is invoked in the
context of a bundle, it uses a special token to find bundle-relative
internal libraries (see @executable_path and friends in `man 1 dyld`). This
is independent of Info.plist, except insofar as existence (not contents) of
that plist is part of Apple's definition of "bundle".

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


Re: [Haskell-cafe] Installing wxHaskel on Snow Leopard

2013-08-08 Thread Brandon Allbery
On Thu, Aug 8, 2013 at 9:54 AM, Eduardo Sato  wrote:

> The only problem now is that I want to distribute a wxHaskell application
> on mac OS X. I tried using macosx-app and cabal-macosx (
> https://github.com/michaelt/cabal-macosx) to make an "app" file. It runs
> fine on my machine, but it fails to run on another computer. I get the
> following error:
>
> Dyld Error Message: Library not loaded:
> /Users/eduardo/.cabal/lib/wxc-0.90.1.0/ghc-7.6.3/libwxc.dylib.
>
> What would be the best way to redistribute wxHaskell apps?
>

This sounds like cabal-macosx was not updated to handle dynamic GHC
libraries. (GHC used to default to static; OS X was one of the first
platforms to switch to default dynamic.) I know in theory how to deal with
this (copy the necessary libraries into the app bundle and use
install_name_tool to adjust the references to be bundle-relative) but could
not give you exact details.

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


Re: [Haskell-cafe] Alternative name for return

2013-08-06 Thread Brandon Allbery
On Tue, Aug 6, 2013 at 9:10 PM, Richard A. O'Keefe wrote:

> I bet you can find an abundance of C programmers who think that
> "strcmp" is an intuitive name for string comparison (rather than
> compression, say).
>

Them and a small and slowly shrinking group of folks who find it intuitive
because obviously only the first 6 characters of an imported function are
significant :)

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


Re: [Haskell-cafe] Alternative name for return

2013-08-06 Thread Brandon Allbery
On Tue, Aug 6, 2013 at 4:03 AM, J. Stutterheim  wrote:

> I have to admit that I am a bit torn about using `pure`. On the one hand,
> if you actually have a pure value, it feels pretty intuitive to me. But
> what about
>
>   pure (putStrLn "Hi")
>
> `putStrLn "Hi"` is not a pure value... Or is there another way to
> interpret the word pure in this context?
>

I actually have the opposite problem: what's impure about lifting 5 into
Maybe or []? `pure` feels IO-targeted.

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


Re: [Haskell-cafe] Why GHC is written in Happy and not a monadic parser library?

2013-08-02 Thread Brandon Allbery
On Fri, Aug 2, 2013 at 8:49 PM, blackbox.dev.ml
wrote:

> Is there any specific reason why GHC is written in a parser GENERATOR
> (Happy) and not in MONADIC PARSER COMBINATOR (like parsec)?
>
> Is Happy faster / handles better errors / hase some great features or
> anything else?
>

Most probably because GHC predates practical parser combinators. Happy is
just a yacc clone, really; ancient tech. And I would suspect that replacing
the parser at this point could get pretty painful.

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


Re: [Haskell-cafe] Sneaky method for var-arg fns?

2013-07-26 Thread Brandon Allbery
On Fri, Jul 26, 2013 at 5:08 PM, Micah Cowan  wrote:

> I was wondering if there was a way to do it in "pure" Haskell (i.e., no
> GHC pragmas required), and also the specific reason for why the above
> example doesn't work without the pragma (I think it's just that in
> general a -> b is not syntactically allowed for type specifiers within
> instance declarations)?
>

The error message you get without the pragma tells you exactly what's
wrong, and that's not it.

Standard Haskell is *very* conservative about what it allows in an instance
declaration; you may not have literal types, nor may you repeat a type
variable, only things of the form (Type var1 var2 ...) are permitted. (The
(String -> String) is not syntactically a problem; it's read as ((->)
String String) which would conform *if* it didn't use literal types. You
can verify this by rephrasing it in prefix form --- note the error message
uses the infix form even if you phrase it as a prefix!) This is widely seen
as unnecessarily restrictive.

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


Re: [Haskell-cafe] ordNub

2013-07-15 Thread Brandon Allbery
On Mon, Jul 15, 2013 at 10:31 PM, Ivan Lazar Miljenovic <
ivan.miljeno...@gmail.com> wrote:

> If I understand correctly, this function is proposed to be added to
> Data.List which lives in base... but the proposals here are about
> using either Sets from containers or HashSet from
> unordered-containers; I thought base wasn't supposed to depend on any
> other package :/
>

As I understand it, currently we have a double proposal: simple ordNub in
Data.List without external dependencies, and the other one in containers
and/or unordered-containers as appropriate.

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


Re: [Haskell-cafe] ordNub

2013-07-15 Thread Brandon Allbery
On Sun, Jul 14, 2013 at 7:54 AM, Clark Gaebel  wrote:

> Oops sorry I guess my point wasn't clear.
>
> Why ord based when hashable is faster? Then there's no reason this has to
> be in base, it can just be a
>
Did the point about "stable" fly overhead?

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


Re: [Haskell-cafe] getting haddock to cooperate with cpp

2013-07-12 Thread Brandon Allbery
On Fri, Jul 12, 2013 at 2:25 PM, Evan Laforge  wrote:

> In the broader scheme, it seems perverse to be using CPP in the first
> place.  I use it to configure imports and exports, e.g. to swap out a
> driver backend on different OSes, and to export more symbols when
> testing.  Would it make sense to have a haskell version of CPP that
> provides only these features (e.g. just #ifdef, #else, #endif, and
> #define) and leaves out the problematic C comments and backslash
> expectations?
>

You mean http://hackage.haskell.org/package/cpphs ? (although I think it
may still do some of that stuff, it does far less than ANSI demands)

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


Re: [Haskell-cafe] Comparing functions

2013-07-11 Thread Brandon Allbery
On Thu, Jul 11, 2013 at 2:58 PM, Vlatko Basic wrote:

> Hm, I thought it is a pattern match with constant, as in f ('a':xs) ==
>>
>
>  I wonder what you'd make of this definition, then?
>
>  (*) `on` f = \x y -> f x * f y
>
>
> According to the enlightenment above, I'd say (*) is a variable that holds
> some function/operator that is applied on (f x) and (f y),  not the
> multiplication, right?
>

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

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


Re: [Haskell-cafe] Comparing functions

2013-07-11 Thread Brandon Allbery
On Thu, Jul 11, 2013 at 2:11 PM, Vlatko Basic wrote:

> The problem here isn't quite what you think it is; (==) is not a
> constructor, therefore it is a *variable*. It's exactly the same problem as
>
>  a = 5
> -- ...
> foo a = 3 -- this does NOT compare with the previous value of "a";
> it's identical to the next line!
> foo x = x
>
>Hm, I thought it is a pattern match with constant, as in f ('a':xs) ==
>

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

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

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


Re: [Haskell-cafe] Comparing functions

2013-07-11 Thread Brandon Allbery
On Thu, Jul 11, 2013 at 1:33 PM, Vlatko Basic wrote:

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

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

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

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

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


Re: [Haskell-cafe] ghci & ghc -> JS (Emscripten)

2013-07-03 Thread Brandon Allbery
On Wed, Jul 3, 2013 at 6:26 AM, B B  wrote:

> Could you please answer one additional question - why you, while creating
> GHCJS didn't base on emscripten? Why haven't you patched it and created
> custom solution?
>

I'd like to point out that the LLVM code from GHC is CPS-transformed, and
this makes it a nightmare to work with. Already the LLVM optimizer pretty
much fails to do anything: optimizing CPS-transformed code is well-nigh
impossible without knowing what the pre-transformation code was, which
means a GHC-specific optimizer is necessary, or some way to communicate the
code's structure (LLVM actually supports annotations for this, but current
GHC doesn't generate them; I also would expect those annotations to go only
so far without GHC-specific tweaks to LLVM, and in fact I am under the
impression such tweaks have been proposed for inclusion in LLVM).

Similarly I would expect that generating any sort of sensible Javascript
would require something fairly tightly tied to GHC; otherwise the output's
going to have horrible performance because it's not going to understand the
input and will fall back to the slowest but most general translation. (If
it even has such a fallback, instead of simply failing on code that it
doesn't recognize.)

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


Re: [Haskell-cafe] Spam on list??

2013-07-01 Thread Brandon Allbery
On Mon, Jul 1, 2013 at 11:19 AM, Vlatko Basic wrote:

>  Anybody else getting this spam emails from j...@eukor.com every time a
> message is sent to Cafe?
>

Yes, and I'm hoping a list admin steps in soon.

The irony is, it's their *anti*spam filter. They decided to use one of
those obnoxious whitelisting systems that requires all senders to register
with it before it will pass on their mail... but didn't exclude mailing
lists from this. Mailing lists, of course, can't authenticate, so they're
sending all these image-heavy "please whitelist yourself" messages in
Korean to the list submission address *and* not seeing any actual list
traffic.

This is one of the reasons I sometimes wish that use of an active spam
whitelist like this were grounds for disabling the user's email account.
They can't even tell what kind of mess they're making.

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


Re: [Haskell-cafe] question about indentation conventions

2013-07-01 Thread Brandon Allbery
On Mon, Jul 1, 2013 at 9:56 AM, Tikhon Jelvis  wrote:

> I've thought about writing an automatic indenting tool for Haskell (or,
> more accurately, a pretty-printer) for another project I have, and this is
> the main thing that threw me off. While automatic indentation might make
> sense for less expressive languages (Google Go being an extreme example), I
> think it would be too constraining for Haskell. After all, in reasonable
> code, chances are that similar constructs end up meaning wildly different
> things (especially with the advent of pervasive embedded DSLs), so the code
> itself is a poor indicator of its own structure.
>

One might look at the history of the indentation modules for Emacs
haskell-mode. Short version: they gave up, tab iterates through the
possibilities because it's quite impossible to know which one is correct
without a *semantic*, not just syntactic, understanding of the code.
(Which, when you think about it, is pretty much par for the Haskell
language definition. See also the literally impossible brace insertion rule
of Haskell98.)

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


Re: [Haskell-cafe] question about indentation conventions

2013-07-01 Thread Brandon Allbery
On Mon, Jul 1, 2013 at 3:43 AM, Tom Ellis <
tom-lists-haskell-cafe-2...@jaguarpaw.co.uk> wrote:

> > is OK but
> >   f (g x
> >   y z)
> > is not.
>
> It seems to me that this means
>
> f x1 x2
> x3 x4
>
> is not.  The OP was initially asking about this situation.
>

If you wrote that in a do, the compiler would insert a (>>) between the two
lines.

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


Re: [Haskell-cafe] Installing Z3 on OS X 10.8.4 ( Off topic )

2013-07-01 Thread Brandon Allbery
On Mon, Jul 1, 2013 at 8:34 AM, Johannes Waldmann <
waldm...@imn.htwk-leipzig.de> wrote:

> and note that the install script says:
>
> Z3 shared libraries were installed at /usr/local/lib, make sure this
> directory is in your LD_LIBRARY_PATH environment variable.
>

Only applicable on Linux (and setting the OS X equivalent of
LD_LIBRARY_PATH is an absolutely wonderful way to break your system). OS X
compiles full paths to shared objects into binaries, and provides a tool to
change them if the need arises (install_name_tool).

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


Re: [Haskell-cafe] tangential request...

2013-06-22 Thread Brandon Allbery
On Sat, Jun 22, 2013 at 9:49 PM, Michael Orlitzky wrote:

> On 06/22/2013 01:28 PM, Mark Lentczner wrote:
> > 3) Do not resize the terminal window
>
> and
>
> > 5) Take a screen shot of the whole terminal window
>
> are mutually exclusive?
>

No, he wants a window shot, not a whole-screen shot.

What *is* inconsistent is that "do not resize" presumably take it at its
natural size. Users of tiling window managers need not apply

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


Re: [Haskell-cafe] Strange cabal failure

2013-06-18 Thread Brandon Allbery
On Tue, Jun 18, 2013 at 1:57 PM, Jacques Carette wrote:

> In trying to install the lens package, it eventually tries to install
> transformers-compat-0.1.1.1 which in turn depends on transformers-0.3.0.0
> -- however that asksk for
> transformers-0.3.0.0-**3006d6ea13a2c10770bffd4de7a96d**c9
> which 1) is weird, and 2) doesn't exist!'
>
> What gives?
>

The large blob at the end is an ABI hash which is computed when you install
a package. So it would appear that you had transformers-0.3.0.0 installed
and then removed it, but it's still indexed for some reason.

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


Re: [Haskell-cafe] opengl type confusion

2013-06-16 Thread Brandon Allbery
On Sun, Jun 16, 2013 at 4:42 PM,  wrote:

> On Sun, 16 Jun 2013 16:15:25 -0400
> Brandon Allbery  wrote:
> > On Sun, Jun 16, 2013 at 4:03 PM,  wrote:
> > > Changing the declaration to GLdouble -> GLdouble -> GLdouble -> IO()
> and
> > > using
> > > (0.0::GLdouble) fixes it, and I'm not clear on why it's not automagic.
> > >  There are many times I see the
> >
> > I presume the reason the type specification for numeric literals is
> because
> > there is no defaulting (and probably can't be without introducing other
> > strange type issues) for GLdouble.
>
> What I was thinking about, using a very poor choice of words, was this :
>
> *Main> let a = 1
> *Main> :t a
> a :: Integer
> *Main> let a = 1::Double
> *Main> a
> 1.0
> *Main> :t a
> a :: Double
> *Main>
>
> so normally 1 would be interpreted as an int, but if I declare 'a' a
> Double then it gets "promoted" to a Double without me having to call a
> conversion routine explicitly.
>
> That seems automagic to me.
>

No magic involved, although some automation is. Take a look at the
`default` keyword in the Haskell Report (this is the "defaulting" I
mentioned earlier).

http://www.haskell.org/onlinereport/haskell2010/haskellch4.html#x10-790004.3.4

The "default `default`" is `default (Integer, Double)` which means that it
will try to resolve a numeric literal as type Integer, and if it gets a
type error it will try again with type Double.

You should use this same mechanism to make numeric literals work with
OpenGL code: neither Integer nor Double will produce a valid type for the
expression, but at the same time the compiler cannot infer a type because
there are two possibilities (GLfloat and GLdouble). You could therefore add
a declaration `default (Integer, Double, GLdouble)` so that it will try
GLdouble to resolve numeric literals when neither Integer nor Double will
work.

> How can I simply declare 0.0 to be (0.0::GLdouble) and have the
functional call work.  Doesn't a conversion have to be happening, i.e.
shouldn't I really have to do (realToFrac 0.0) ?

The first part I just answered. As to the second, a conversion *is*
happening, implicitly as defined by the language; the question being, to
what type. A numeric literal has type (Num a => a), implemented by
inserting a call to `fromIntegral` for literals without decimal points and
`fromRational` for others. But the compiler can't always work out what `a`
is in (Num a => a) without some help (the aforementioned `default`
declaration).

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


Re: [Haskell-cafe] opengl type confusion

2013-06-16 Thread Brandon Allbery
On Sun, Jun 16, 2013 at 4:03 PM,  wrote:

> Changing the declaration to GLdouble -> GLdouble -> GLdouble -> IO() and
> using
> (0.0::GLdouble) fixes it, and I'm not clear on why it's not automagic.
>  There are many times I see the


Haskell never "automagic"s types in that context; if it expects GLdouble,
it expects GLdouble. Pretending it's Double will not work. It "would" in
the specific case that GLdouble were actually a type synonym for Double;
however, for performance reasons it is not. Haskell Double is not directly
usable from the C-based API used by OpenGL, so GLdouble is a type synonym
for CDouble which is.

compiler doing type conversion an numerican arguments although sometimes
> the occasional fracSomethingIntegralorOther is required.
>

I presume the reason the type specification for numeric literals is because
there is no defaulting (and probably can't be without introducing other
strange type issues) for GLdouble.

In any case, the very fact that you refer to "automagic" and "type
conversion" indicates that you don't really have an understanding of how
Haskell's numeric types work; this will lead you into not only this kind of
confusion, but worse problems later. In particular, you're going to get
into dreadful messes where you expect Haskell to transparently deal with
strange combinations of numeric types as if Haskell were (almost-typeless)
Perl or something, and you'll have real trouble getting that code to work
until you sit down and figure out how strong typing and Haskell's numeric
typeclasses interact.

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


Re: [Haskell-cafe] Automating Hackage accounts

2013-06-13 Thread Brandon Allbery
On Thu, Jun 13, 2013 at 10:48 AM, Niklas Hambüchen  wrote:

> > As for the user account creation and uploading packages you don't own,
> > Hackage 2 (any day now) has fixes for both.
>
> Does Hackage 2 have SSL at least for the web interface?


Doesn't look like it. :(

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


Re: [Haskell-cafe] How to write a pure String to String function in Haskell FFI to C++

2013-06-02 Thread Brandon Allbery
On Sun, Jun 2, 2013 at 8:01 PM, Thomas Davie  wrote:

> On 2 Jun 2013, at 16:48, Brandon Allbery  wrote:
>
> (String is a linked list of Char, which is also not a C char; it is a
> constructor and a machine word large enough to hold a Unicode codepoint.
> And because Haskell is non-strict, any part of that linked list can be an
> unevaluated thunk which requires forcing the evaluation of arbitrary
> Haskell code elsewhere to "reify" the value; this obviously cannot be done
> in the middle of random C code, so it must be done during marshalling.)
>
>
> I'm not convinced that that's "obvious" – though it certainly requires
> functions (that go through the FFI) to grab each character at a time.
>

I think you underestimate the complexity of the Haskell runtime and the
interactions between it and the FFI. Admittedly it is probably not
"obvious" in the sense of "anyone can tell without knowing anything about
it that it can't possibly work", but it should be at least somewhat obvious
to someone who sees why there needs to be an FFI in the first place that
the situation is not trivial, and that they probably should not blindly
assume that the only reason one can't just pass Haskell values directly to
C is that some GHC developer was feeling lazy at the time.

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


Re: [Haskell-cafe] How to write a pure String to String function in Haskell FFI to C++

2013-06-02 Thread Brandon Allbery
On Sun, Jun 2, 2013 at 7:22 PM, Ting Lei  wrote:

> In particular, I wanted to avoid having an IO in the return type because
> introducing the impurity
> (by that I mean the IO monad) for this simple task is logically
> unnecessary. All examples involing
>

Anything that comes into or goes out of a Haskell program is in IO, period.
If you have an FFI function which is guaranteed to not change anything but
its parameters and those only in a pure way, then you can use
unsafeLocalState to "hide" the IO; but claiming that when it's not true can
lead to problems ranging from incorrect results to core dumps, so don't try
to lie about it.


>  a C string I have seen so far involve returning an IO something or Ptr
> which cannot be converted back to a pure String.
>

Haskell String-s are *not* C strings. Not even slightly. C cannot work with
Haskell's String type directly at all. Some kind of marshaling is
absolutely necessary; there are functions in Foreign.Marshal.String that
will marshal Haskell String-s to and from C strings.

(String is a linked list of Char, which is also not a C char; it is a
constructor and a machine word large enough to hold a Unicode codepoint.
And because Haskell is non-strict, any part of that linked list can be an
unevaluated thunk which requires forcing the evaluation of arbitrary
Haskell code elsewhere to "reify" the value; this obviously cannot be done
in the middle of random C code, so it must be done during marshaling.)

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


Re: [Haskell-cafe] Different answers on different machines

2013-06-01 Thread Brandon Allbery
On Sat, Jun 1, 2013 at 1:55 PM,  wrote:

> a Dell laptop and a desktop.  I compiled this message with ghc -O2
> --make ex429.lhs and ran it on each machine.  On the Dell I get:
>
> 136342232
> ./ex429  8.66s user 0.02s system 99% cpu 8.695 total
>
> When I run this exact same file on the desktop, I get:
>
> 98792821
> ./ex429  6.50s user 0.03s system 99% cpu 6.537 total
>
> Which happens to be the right answer.  But WHY is the output from the
> Dell different?
>
(hardware description elided)

You're missing one piece of information: do you have the 32-bit or the
64-bit ghc installed on each machine?

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


Re: [Haskell-cafe] using a win32 dll (Happy too soon)

2013-05-30 Thread Brandon Allbery
On Thu, May 30, 2013 at 11:46 AM, Kees Bleijenberg <
k.bleijenb...@lijbrandt.nl> wrote:

> Brandon, thanks again for your explanation
> Are you sure about the non existing search order for dynamic loaded dll’s?
> I.e.
> http://msdn.microsoft.com/en-us/library/windows/desktop/ms682586(v=vs.85).aspx#standard_search_order_for_desktop_applicationssays
>  there is a search order, starting with the current directory (I think).
>

There is a search order. What I said is that there are no standard
locations to install things. That is, every library package stows stuff in
its own directory structure and no compiler can possibly know all the
places it needs to look to find every library off in its own directory.


> I don’t understand why the linker needs to see the dll anyway.


Because it's better to catch "that symbol doesn't exist" at build time
instead of throwing an ugly error at runtime, among other things.


> possible in Delphi. Is Haskell dynamic loading more limited?
>

There are ways to do that kind of dynamic linking; this is not one of them.
C and C++ don't automatically dynload the way you're thinking either,
because you should test for the DLL you're distributing (you are
distributing it, right, not forcing the end user on a wild goose chase to
find their own copy of the DLL, hoping it's the right/compatible version,
and figure out where to put it so your program will run?) being the right
one *when you build the program*, not defer that test until it is run.

If you think about it, this is very similar to doing your type checking at
compile time instead of runtime. If you want lazy type checking, why are
you using Haskell? If you want lazy library checking, why are you using a
compiler?

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


Re: [Haskell-cafe] using a win32 dll (Happy too soon)

2013-05-30 Thread Brandon Allbery
On Thu, May 30, 2013 at 3:15 AM, Kees Bleijenberg <
k.bleijenb...@lijbrandt.nl> wrote:

> argument. The dll is in the PATH. I don't understand why it needs the -L
> argument. I'll figure this out later. If I use -lglasPng.dll (additional
> .dll) it doesn't work either.
>

Unix has standard places to install and search for libraries; Windows
doesn't, and almost every library that doesn't come with your build system
will need at least one -L option to tell the linker where to find it.

As I mentioned in my first message, it looks for multiple file names with
-l: first it tries a .dll, then it tries a .lib (static library or import
library for older DLLs). It does this mechanically; if you also include the
.dll suffix, then it looks for library.dll.dll and library.dll.lib, which
is almost certainly wrong.

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


Re: [Haskell-cafe] using a win32 dll (Happy too soon)

2013-05-29 Thread Brandon Allbery
On Wed, May 29, 2013 at 9:40 AM, Kees Bleijenberg <
k.bleijenb...@lijbrandt.nl> wrote:

> If I compile with ghc --make testGlasPng.hs –lglasPng I get: ….\ld.exe:
> cannot find –lglasPng. Collect 2: ld returned 1 exit status.
>
> **
>
> Ld can’t find lglasPng (with the l in front, does it trim the l?). Why?
> Okay I try
>

It's reproducing the thing passed to it, rather than outputting both the
dll and implib versions that it actually looks for. Same happens on
unixlikes where it's looking for a .so/.dylib/whatever or a .a.


>
> ghc --make testGlasPng.hs –L I get:
>

Not quite right; -L identifies a *directory* to search, then you must
specify the actual filename afterward.


> 
>
> testGlasPng.o: fake: (.text + 0x82) :undefined reference to
> ‘getPngVersion@0’. I think it has found  the
>

This just means it can't find the symbol; it does not mean it necessarily
found the DLL.


> I run ghc on a 64 bits computer. The dll is 32 bits. Is that the problem?
>

That can certainly be a problem, yes, and is likely why it wasn't found
with the first one. But it's not so much what kind of machine you are on,
as what kind of ghc you are using: a 64-bit ghc cannot link 32-bit
libraries, and vice versa. But a 32-bit ghc and toolchain will work fine on
a 64-bit system, aside from not linking 64-bit DLLs.

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


Re: [Haskell-cafe] list comprehension doesn't work

2013-05-14 Thread Brandon Allbery
On Tue, May 14, 2013 at 11:17 AM, John  wrote:

> listPairs = [(a*b, y) | a <- [0..], b <- [0..], (a*b) > 5, (a*b) < 500,
> (y*y) < 1001, mod y x == 0]
>
> Now I have it as you said, however the compiler complains about all y and x
> and says they are NOT in scope.
>
> Why is it so? I can't see any problem with that...
>

I don't see any definitions of x or y there. (Note that you have replaced x
with a*b.)

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


Re: [Haskell-cafe] ghci: Difference in garbage collection etc. between REPL and function

2013-05-09 Thread Brandon Allbery
On Thu, May 9, 2013 at 10:19 AM, Niklas Hambüchen  wrote:

> On 09/05/13 20:50, Brandon Allbery wrote:
> > ghci is in many ways like an endless (or at least until ":l"/":r")
> > do-block. In particular, the handle remains in scope after you run your
> > commands at the prompt, so it is not garbage collected.  If you enclose
> > it into its own do block, this introduces local scope and the handle
> > goes out of scope and is garbage collected at the end.
>
> I am not sure how the handle is relevant - I do not expect it to garbage
> collected before the close or rely on that, and my problem happens
> earlier already.
>

You said 'garbage in the handle'... but in any case it applies to all the
bindings, not just to that one. Generalize.

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


Re: [Haskell-cafe] ghci: Difference in garbage collection etc. between REPL and function

2013-05-09 Thread Brandon Allbery
On Wed, May 8, 2013 at 9:54 PM, Niklas Hambüchen  wrote:

> If I run these steps one by one in ghci, garbage ends up in my handle as
> expected.
>
> However, if I "let main = do ..." this whole block in order to pack it
> in a test case, it does not happen, neither in ghci nor ghc.
>

ghci is in many ways like an endless (or at least until ":l"/":r")
do-block. In particular, the handle remains in scope after you run your
commands at the prompt, so it is not garbage collected.  If you enclose it
into its own do block, this introduces local scope and the handle goes out
of scope and is garbage collected at the end.

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


Re: [Haskell-cafe] Fwd: Backward compatibility

2013-05-05 Thread Brandon Allbery
On Sun, May 5, 2013 at 7:55 AM, Raphael Gaschignard wrote:

> Forgive me if I'm wrong, but I feel like I've seen such "suggestions" in
> GHC errors before.
>
> If so, does that mean there's some sort of mechanism in the compiler
> already in place for such error recognition? Like some simple pattern
> stuff?  If not, I think that it might not be bad to consider this stuff
> (misused packaged, changed semantics that create compiler errors), and to
> put something into place for future modifications. This could make it a lot
> easier to deal with unmaintained code.
>

There's some very limited capability now; the GHC folks are tossing around
ideas for something more general like that.

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


Re: [Haskell-cafe] runhaskell flags: What is going on?

2013-05-04 Thread Brandon Allbery
Bleh, I could have sworn that thing had a real usage message at some
point...​ which means there is in fact a problem and you should file a bug
against runhaskell.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Backward compatibility

2013-05-03 Thread Brandon Allbery
On Fri, May 3, 2013 at 10:54 AM, Guy  wrote:

> http://hackage.haskell.org/**trac/ghc/wiki/**DefaultSuperclassInstances
>
> I'm surprised that the various superclass proposals haven't got more
> attention, seeing as it would allow for this kind of class hierarchy
> clean-up without breaking lots of code.


IIRC they've been tried and found to actually cause more backward
compatibility issues than they solve because there are so many packages
which have created their own instances, and nobody's found a workaround
that doesn't either do that or lead to bizarre type errors.

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


Re: [Haskell-cafe] runhaskell flags: What is going on?

2013-05-03 Thread Brandon Allbery
On Fri, May 3, 2013 at 10:35 AM, Niklas Hambüchen  wrote:

> > runhaskell -fno-warn-unused-matches Myfile.hs
> [some compile error]
>
> > runhaskell -fno-warn-unused-matches Myfile.hs
> [no output whatsoever but exit code 127]
>
> > runhaskell -asdf Myfile.hs
> ghc: unrecognised flags: -asdf
>
> > runhaskell -fasdf Myfile.hs
> [no output whatsoever but exit code 127]
>
> Not sure if that's how it should work or missing error reporting?
>

If you type just 'runhaskell' you will get an error message which explains
what is going on. (The short version is, -f has multiple meanings; some of
them apply to runhaskell, and some to the underlying ghc.)

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


Re: [Haskell-cafe] Backward compatibility

2013-05-03 Thread Brandon Allbery
On Fri, May 3, 2013 at 5:30 AM, Adrian May
wrote:

> How about this: can you guys give me a detailed example of a justified
> deprecation: one so extremely obviously called for that even I would agree.
> I just want to understand the kind of logic that's applied over these
> things.
>

This might not be possible because your notion of a justified change may
not align with other people's. IIRC the removal of the Show constraint on
Num was driven by type level natural numbers? which matter to the type
hackers but not to someone whose main concern is getting an unmaintained
web interface running. (OTOH it also may not have any effect on said web
server, since it mostly affected people who take the somewhat risky action
of defining their own Num instances; I suspect the exceptions change would
have more impact on web stuff.)

As for the exceptions stuff, that was a multi-step change. Exception
handling was somewhat unprincipled and came in two forms, which used the
same function names but in different ways. There was support for IO
exceptions in the Prelude and conflicting support for general exceptions,
which behaved somewhat differently when handed an IO exception, in
Control.Exception. One key behavior was that you had to handle all
exceptions or none at all; the only way to choose specific exceptions was
to handle all of them, inspect the exception object, and rethrow if it
wasn't one you wanted to handle. And inspecting the exception object to see
what it had in it could be tricky at times, because there wasn't much
guidance with respect to user defined exceptions and some library
exceptions did things slightly differently from the ones in the base.

The exception cleanup made IO exceptions and other exceptions behave
consistently and got rid of the conflicting definitions. This did require
source changes, as anyone relying on the Prelude exceptions had to add an
import of Control.Exception and anyone using old-style exceptions generally
had to add a type annotation to their handler; more ideally, they'd rewrite
their exception code to handle specific exceptions or exception classes
instead of poking at the exception object to determine whether it was one
they cared about or not --- but this was not necessary to get older code
running again, only the added type annotation was necessary.

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


Re: [Haskell-cafe] Backward compatibility

2013-05-02 Thread Brandon Allbery
On Thu, May 2, 2013 at 10:36 AM, Adrian May
wrote:

> I think you're missing the point of the platform!
>>
>
> I suppose I did miss the point of the platform: I was trying to build it,
> which requires at least part of the
>

Having to build it already indicates that something is wrong, unless you're
porting to an unsupported OS/hardware.


> platform. As I say, the reason I was trying to build it was that I wrongly
> blamed the ubuntu package for
>

That said, may I point out that the Ubuntu packages *are* broken? They
shipped a mangled Platform which can't be relied on for much; instead of a
well-tested set of packages, they took a good Platform and replaced bits
with minimal testing. Yes, this has actually caused problems for people.

Yes there are times when something has to change. I acknowledged that in my
> original post. But I see no evidence whatsoever that anybody in control of
> Haskell is holding fire even on things as innocent as getPackageId or as
> ubiquitous as the prelude. I'm not asking for the opposite extreme of
> conservatism, just a bit of common sense instead of this bloodbath.
>

You're assuming here that someone deliberately targeted your favorite pet.
I don't know the details but I VERY STRONGLY doubt anyone said "oh, we
should break that function". But I ALSO find it likely that it was the
victim of something sufficiently pervasive that the options were "break it"
or "live with something else being broken forever, just like Perl vs.
cpanel!"

This, sadly, is the real world. The holy grail of fixing bugs without
breaking any program ever anywhere is impossible, and even "fix this bug
without breaking many other programs" is extremely unlikely. Your choices
are this, or Perl/PHP "we do not dare fix bugs or misdesigns because
someone's pet program will die".

(Other examples of this:

- Python 3. Note how many existing Python packages still require Python 2.
- The C and C++ standards are increasingly Byzantine due in large part to
backward compatibility issues; but I'm guessing from your complaints that
this is your ideal model because "old programs still work". Lucky you, you
can happily pretend that it's because they have found some magical way to
do the fundamentally impossible --- right up until reality bites back.
)

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


Re: [Haskell-cafe] Backward compatibility

2013-05-02 Thread Brandon Allbery
On Thu, May 2, 2013 at 1:27 AM, Adrian May
wrote:

> Let's face it: this decision to change the default syntax in GHC7 means
> that right now Haskell looks about as stable as Ruby on Rails.
>
> I just tried to use Flippi. It broke because of the syntax change so I
> tried WASH. I couldn't even install it because of the syntax change. I
> persisted for a while but gave up because getPackageId doesn't exist in any
> form at all anymore. This was only the install script: what would WASH
> itself have in store for me to get my brain around?
>

I'm going to give you the flip side of this one.

I've been active in the Perl community (admittedly in something of an off
and on fashion for health reasons) for years. Perl 5 is in some ways the
epitome of "maintain backward compatibility": there is a lot of Perl code
out there that was written under Perl 4 or earlier. (cpanel, I'm looking at
you. Among others. I recently got to debug some code related to someone's
RADIUS server that looked like it hadn't been touched since perl3.)

And this is the direct cause of the Perl ecosystem being a sewer. Nobody is
willing to take the step of making Perl default to the eminently sane
behavior of checking for invalid inputs, because it will "break" too much
existing (already horribly broken, in reality) code. Nobody will risk
disabling the walking security hole and encouragement of sloppy, buggy code
that is Perl's 2-argument open(). (If you ever wondered why Perl 6 decided
to throw out source compatibility, here's your reason.)

The Haskell98 ecosystem wasn't nearly that bad, but maintaining
compatibility with it did prevent fixing various flaws in things like
exception handling. Between the two, I'd rather see older code broken in
the name of current code actually working correctly. And in Haskell I get a
lot of help from the compiler to bring that older code up to date.

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


Re: [Haskell-cafe] Why were datatype contexts removed instead of "fixing them"?

2013-04-28 Thread Brandon Allbery
On Sun, Apr 28, 2013 at 3:59 AM, harry  wrote:

> Dan Doel  gmail.com> writes:
>
> > However, another thing to consider is that getting rid of data type
> contexts was accepted into the language standard.
>
> ... which means that implementers should be free to "fix" data type
> contexts
> however they like, as they are now complier extensions which won't conflict
> with standard Haskell.


Except that people do build older programs with newer Haskell compilers,
and it's bad to "repurpose" a syntax like that because it leads to strange
errors.

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


Re: [Haskell-cafe] Request for help: Recompile of ghc producing "...-ghc7.4.2.so"s, which break project builds.

2013-04-27 Thread Brandon Allbery
On Sat, Apr 27, 2013 at 11:47 AM, David Banas  wrote:

> dbanas@dbanas-lap:~/prj/AMI-Tool$ make
> rm -f libami.so
> ghc -o libami.so -shared -dynamic -package parsec -lHSrts -lm -lffi -lrt
> AMIParse.o AMIModel.o ami_model.o ExmplUsrModel.o Filter.o
> dbanas@dbanas-lap:~/prj/AMI-Tool$
>
>
> However, I'm a little confused as to why the "-package parsec" isn't
> triggering the same issue, since the parsec dynamic libraries were given
> the same "-ghc7.4.2" suffix:
>

That would be because the parsec library contains the correct invocation
already, but above you are telling the linker to look for libHSrts.{so,a}
with the explicit -l option. You would need to change it to
```-lHSrts-ghc7.4.2```.

Perhaps ghc needs an option to include the correct runtime support
libraries in this case; certainly, having to specify all of those in the
build command is ugly and fragile even without mangled shared object names.

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


Re: [Haskell-cafe] Why were datatype contexts removed instead of "fixing them"?

2013-04-25 Thread Brandon Allbery
On Thu, Apr 25, 2013 at 6:38 AM, harry  wrote:

> If I understand correctly, the problem with datatype contexts is that if we
> have e.g.
>   data Eq a => Foo a = Foo a
> the constraint Eq a is thrown away after a Foo is constructed, and any
> method using Foos must repeat Eq a in its type signature.
>
> Why were these contexts removed from the language, instead of "fixing"
> them?
>

As I understand it, it's because fixing them involves passing around a
dictionary along with the data, and you can't do that with a standard
declaration (it amounts to an extra chunk of data that's only *sometimes*
wanted, and that "sometimes" complicates things). GADTs already have to
pass around extra data in order to support their constructors and
destructors; and, being new and not part of the standard, they don't have
backward compatibility or standards compatibility issues, so they can get
away with including the extra dictionary without breaking existing programs.

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


Re: [Haskell-cafe] cabal-install 1.16.0.2 on Mac

2013-04-11 Thread Brandon Allbery
On Thu, Apr 11, 2013 at 7:41 PM, Richard A. O'Keefe wrote:

> The basic problem is that the University has a strict policy
> that academic staff must not have root access on any machine
> that is connected to the University network.  I was given an
> administrator account so that I could resume the printer and
> install (some) stuff, but /Developer is owned by root, and I
> will be given root access on the Greek Calends.
>
> I would have thought that many organisations would have similar
> policies.
>

Well, yes (I was one of those admins, although not at your university, for
many years), but if they are installing machines with both Xcode 4.6 under
/Applications and Xcode 4.1 or earlier under /Developer, they are
installing broken machines that will fail to build many packages and where
Xcode may malfunction. /Developer should not exist on a machine with Xcode
4.2 or later installed, at all. You should contact an administrator about
this and have them fix both installed machines and their installation
images or maintenance routines (whatever they went with for OS X).

sudo /Developer/Library/uninstall-devtools --mode=all

If they need an official reference on this, I can dig up the relevant Apple
knowledge base article.

> On 12/04/2013, at 2:44 AM, Brandon Allbery wrote:
> (Newer Xcode should actually complain and tell you to run the removal
script on startup, because its presence can even break Xcode under some
circumstances.)
>
> 4.6.1 was the latest available in March when I installed it,
> and it _didn't_ complain or tell me to run any removal script.

I have heard that it is sometimes inconsistent about this; sadly, just
because it didn't notice the older version doesn't mean the older version
won't cause breakage. (As you saw.)

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


Re: [Haskell-cafe] cabal-install 1.16.0.2 on Mac

2013-04-11 Thread Brandon Allbery
On Thu, Apr 11, 2013 at 1:19 AM, Richard A. O'Keefe wrote:

> On 11/04/2013, at 12:56 PM, Brandon Allbery wrote:
> > Xcode 4.2 and on do not use /Developer at all. You have an older Xcode
> on your system somehow, which does not understand newer object files; you
> should remove the entire /Developer tree. (Xcode, in order to be
> distributable via the App Store, is completely self-contained in
> /Applications/Xcode.app.)
>
> Unfortunately, I cannot.  I _am_ able to install stuff, but uninstalling
> generally gives me problems, and removing /Developer is something I'm not
> allowed to do.
>

I think you need to discuss that with whoever made that dictum; requiring
that a system be broken is not generally a good idea. Many software
packages will find it and use outdated programs or frameworks as a result.
It really needs to not be there at all.

(Newer Xcode should actually complain and tell you to run the removal
script on startup, because its presence can even break Xcode under some
circumstances.)

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


Re: [Haskell-cafe] exp implementation

2013-04-11 Thread Brandon Allbery
On Thu, Apr 11, 2013 at 1:38 AM, Christopher Howard <
christopher.how...@frigidcode.com> wrote:

> Hi. For my own learning, I wanted to see how the exp function is
> implemented in GHC. I have GHC 7.4.1 source code open, but I'm having
> trouble figuring out which file the actual function definition is in. I see
>
>  expFloat(F# x) = F# (expFloat# x)
>

expFloat# is likely a primop; good luck Primops aka primitive
operations are generally implemented in the compiler backend as assembly
language or Cmm code. Untangling that part of ghc makes my head swim. >.>

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


Re: [Haskell-cafe] cabal-install 1.16.0.2 on Mac

2013-04-10 Thread Brandon Allbery
On Wed, Apr 10, 2013 at 8:36 PM, Richard A. O'Keefe wrote:

> /Developer/usr/bin/strip: object: /home/cshome/o/ok/.cabal/bin/cabal
> malformed object (unknown load command 15)
>

Xcode 4.2 and on do not use /Developer at all. You have an older Xcode on
your system somehow, which does not understand newer object files; you
should remove the entire /Developer tree. (Xcode, in order to be
distributable via the App Store, is completely self-contained in
/Applications/Xcode.app.)

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


Re: [Haskell-cafe] Automated Differentiation of Matrices (hmatrix)

2013-04-10 Thread Brandon Allbery
On Wed, Apr 10, 2013 at 12:39 PM, Dominic Steinitz wrote:

> :1:6:
> Could not deduce (repa-3.2.3.1:Data.Array.Repa.Eval.Elt.Elt
> (ad-3.4:Numeric.AD.Internal.Types.AD s a))
>
> DANGER WILL ROBINSON!

It's showing package names+versions on the types; this usually means you
have multiple versions of those packages installed, and ghc / ghci is
confused as to which one to use.

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


Re: [Haskell-cafe] Bug in Network package

2013-04-10 Thread Brandon Allbery
On Wed, Apr 10, 2013 at 3:26 AM, Florian Hofmann <
fhofm...@techfak.uni-bielefeld.de> wrote:

> I might be mistaken, but is there a bug in the Show instance of PortNum?
>

Not a bug, an annoying misdesign (IMO). A PortNum is actually in network
byte order. If you extract it, you get the original port; if you simply
show it, you see it byteswapped on little-endian platforms.

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


Re: [Haskell-cafe] llvm-3.0.1.0 installation on Mac

2013-04-08 Thread Brandon Allbery
On Mon, Apr 8, 2013 at 1:32 AM, Luke Evans  wrote:

> Unfortunately, it looks like
>
> /Library/Frameworks/GHC.framework/Versions/7.4.2-x86_64/usr/lib/ghc-7.4.2/libffi.dylib
> is pointing to the dodgy library too, e.g.:
>
> > otool
> -L 
> /Library/Frameworks/GHC.framework/Versions/7.4.2-x86_64/usr/lib/ghc-7.4.2/libffi.dylib
> /Users/ian/zz64/ghc-7.4.2/libffi/build/inst/lib/libffi.5.dylib
> (compatibility version 6.0.0, current version 6.10.0)
> /usr/lib/libSystem.B.dylib (compatibility version 1.0.0, current version
> 159.1.0)
>
> Not sure what to patch the first reference in that one to.
>

To itself; that's actually the internal reference that gets compiled into
the others, and as such is the actual source of the problem. (In an ELF
shared object, that would be the soname. Note that it *must* be a full path
on OS X, unlike Linux/ELF.)

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


Re: [Haskell-cafe] llvm-3.0.1.0 installation on Mac

2013-04-07 Thread Brandon Allbery
On Mon, Apr 8, 2013 at 12:10 AM, Luke Evans  wrote:

> Unfortunately, it looks like my cabal build failure occurs in a temporary
> and very short-lived directory.  So presumably the dodgy FFI gets copied
> into there from elsewhere.  I wonder if I can find the source...


It's running an executable it seems to have built to generate something
else for the build, so I suspect you are in fact seeing the ghc bug and you
should fix the ghc reference. If you installed the official HP package, you
need to find libHSrts-ghc7.4.2.dylib somewhere under /Library/Haskell and
use install_name_tool on that.

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


Re: [Haskell-cafe] Why is "Cont" out of scope?

2013-04-02 Thread Brandon Allbery
On Tue, Apr 2, 2013 at 8:37 PM, Daryoush Mehrtash wrote:

> I am trying to use the Cont in Control.Monad.Cont but it seems to be
> missing
>
> Prelude> import Control.Monad.Cont
> Prelude Control.Monad.Cont> :t Cont
>
>
It's gone; try "cont" (lowercase).

mtl2 replaced the old standalone monads with monad transformers over the
Identity monad (so Cont is a type alias for ContT Identity); however, it's
not possible to create data constructors for type aliases, so the Cont data
constructor is gone and a "cont" smart constructor has taken its place.

Prelude Control.Monad.Cont> :t cont
cont :: ((a -> r) -> r) -> Cont r a

The same is true of State, Reader, and Writer.

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


Re: [Haskell-cafe] Make a DSL serializable

2013-03-25 Thread Brandon Allbery
On Mon, Mar 25, 2013 at 8:53 AM, Corentin Dupont
wrote:

> Workflow is impressive! I didn't know you could serialize IO
> states/computations.


In certain constrained cases you can. General case, as I said earlier, is
kinda impossible without serializing the entire machine state.

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


Re: [Haskell-cafe] Make a DSL serializable

2013-03-24 Thread Brandon Allbery
On Sun, Mar 24, 2013 at 5:44 PM, Corentin Dupont
wrote:

> But I always bothered me that this state is not serializable...


I am not quite sure how to respond to that. You seem to be asking for magic.

That kind of state has never been sanely serializeable. Not in Haskell, not
anywhere else. The usual hack is to dump an entire memory image to disk,
either as an executable (see "gcore" and "undump"; also see how the GNU
emacs build dumps a "preloaded" emacs executable) or by dumping the data
segment as raw bytes and reloading it as such (which doesn't work so well
in modern demand paged executables; it can work better with a virtual
machine environment, and various Lisp and Smalltalk implementations dump
and reload their raw VM images this way).

I would not be surprised if what you seem to be asking for turns out to be
yet another guise of the halting problem.

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


Re: [Haskell-cafe] Make a DSL serializable

2013-03-24 Thread Brandon Allbery
On Sun, Mar 24, 2013 at 4:16 PM, Corentin Dupont
wrote:

> Hi Daniel,
> in my game the handlers are supplied by the players as part of little
> programs that they submit. An haskell interpreter is reading the program
> code submitted and inserts it in the game.
> So there is an infinite number of handlers...
>

You might store both the compiled code and the originally submitted code,
and serialize the latter in a form that restart can recompile. I don't
think that can be any less safe than the original
submission/compilation/insertion.

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


Re: [Haskell-cafe] Enumerating functions at runtime

2013-03-23 Thread Brandon Allbery
On Sat, Mar 23, 2013 at 11:26 PM, Luke Evans  wrote:

> I'm curious about using Haskell for metaprogramming.
>
> It looks like I can dynamically compile, load and run some Haskell with
> the plugins package.  Actually I've briefly tried this and it seems to work
> for some simple cases at least.
> Now I would like to be able to enumerate precompiled public functions in
> modules that I might use as building blocks in such dynamic compilation.
>  So far I'm not seeing anything that does this directly.
> Can anyone provide some pointers?
>

I'm not aware of any canned solutions, but one way you could do it is to
enumerate the symbol table of a compiled module and z-decode symbols;
functions get their types z-encoded into their symbol table names. A more
likely useful way is to extract them from the .hi file; there should be
functions in ghc-api and likely in hint to do this, since the compiler must
do so as part of importing a module; or at worst, you can use ghc
-print-iface to decode a .hi file to text and extract the information that
way.

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


Re: [Haskell-cafe] Compiled program using OpenGL fails to trigger GPU switch on Mac, but works in GHCi

2013-03-20 Thread Brandon Allbery
On Wed, Mar 20, 2013 at 9:02 AM, Jesper Särnesjö  wrote:

> This solution seems to work perfectly for me. Since the foreign code
> is allowed to run uninterrupted, the GPU switch happens, and since the
> GUI actions stay on the main thread, the program's window responds to
> keyboard and mouse input correctly.
>

If that's correct, then I think you have found a bug in the GHC runtime: my
understanding is that the timers should be disabled while foreign code is
running, specifically to avoid confusing code that has no clue that there
is another runtime involved.

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


Re: [Haskell-cafe] Specialized Computer Architecture - A Question

2013-03-18 Thread Brandon Allbery
On Mon, Mar 18, 2013 at 4:31 PM, OWP  wrote:

> Let me rephrase that, of course they will survive politically.  People
> built these tools and if built, they will be use but will they survive
> efficiently?   In the future, if a particular specialized architecture
> is somewhat better than the rest on it's own merit for a particular
> need while the stock architecture is reaching a
> point of low returns for all the energy put into it - could the
> specialized architecture reach a point where it becomes useful?  Could
> there be a competitive advantage to specialized architecture if
> Moore's Law were to go away?
>

There is now, in some narrow specializations. GPUs and DSP come to mind ---
while both are also done on commodity CPUs to some extent, the specialized
architectures are used where speed is of the essence. (DSP started out on
specialized architectures, but many commodity uses are on commodity
architectures these days, reserving the specialized ones to those niches
that require them.)

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


Re: [Haskell-cafe] Compiled program using OpenGL fails to trigger GPU switch on Mac, but works in GHCi

2013-03-17 Thread Brandon Allbery
On Sun, Mar 17, 2013 at 7:58 PM, Jason Dagit  wrote:

> On Sat, Mar 16, 2013 at 6:53 PM, Jesper Särnesjö wrote:
>
>> To be clear, I think this isn't really an OpenGL problem, but rather
>> one related to FFI or event handling. If anyone could explain to me,The
>> release notes for 7.0.1 said this about that flag:
>
> There is a new -fno-ghci-sandbox flag, which stops GHCi running
> computations in a separate thread. In particular, this is useful for GLUT
> on OS X, which only works if being run on the main thread.
>

Worth noting is that Jesper said it *works* in ghci, and fails when
compiled

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


Re: [Haskell-cafe] cabal install oddities

2013-03-12 Thread Brandon Allbery
On Tue, Mar 12, 2013 at 3:21 PM, Tycho Andersen  wrote:

> Below is some sample output from a failing package:
>
> ps168825:~/playground$ cabal install network
> Resolving dependencies...
> Configuring network-2.4.1.2...
> configure: WARNING: unrecognized options: --with-compiler, --with-gcc
> checking build system type... x86_64-unknown-linux-gnu
> checking host system type... x86_64-unknown-linux-gnu
> checking for gcc... gcc
> checking whether the C compiler works... yes
> checking for C compiler default output file name... a.out
> checking for suffix of executables...
> checking whether we are cross compiling... configure: error: in
> `/tmp/network-2.4.1.2-28534/network-2.4.1.2':
> configure: error: cannot run C compiled programs.
>

"cabal install" unpacks a package into /tmp in order to build it. My guess
is your OS has /tmp mounted noexec. I don't know offhand how you override
this in cabal.

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


Re: [Haskell-cafe] Overloading

2013-03-12 Thread Brandon Allbery
On Tue, Mar 12, 2013 at 1:52 PM, Carlos Camarao wrote:

> Sorry, I think my sentence:
> "To define (+) as an overloaded operator in Haskell,
>   you have to define and use a type class."
> is not quite correct.  I meant that to define any operator in Haskell you
> have to
> have a type class defined with that operator as member.
>

What? An operator is just an infix function, taken from the set of symbols.
Any function can be an operator (and is, via `func` syntax). No typeclass
is required to define a random operator.

What did you really mean to say there?

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


Re: [Haskell-cafe] building darcs failed (Unable to link against the iconv library)

2013-03-03 Thread Brandon Allbery
On Sun, Mar 3, 2013 at 1:59 PM, Dmitry Malikov wrote:

>  On 03/03/2013 10:56 PM, Brandon Allbery wrote:
>
> On Sun, Mar 3, 2013 at 10:21 AM, Dmitry Malikov wrote:
>
>> checking  whether  to  use  -liconv...  setup:  Unable  to  link  against
>>  the  iconv  library.
>>
>> What is actually going on here? Iconv libraries already installed with
>> libc6 package.
>>
>
>  Linux distinguishes between runtime and linkable libraries; you probably
> need to install the libc6-dev package to get the latter. (This is not a
> Haskell-specific issue; configure is using a C
>
> But libc6-dev is already the newest version.
>

Then you'll have to check config.log (this probably means doing the build
manually with "cabal unpack darcs"  and then running "cabal install"
without a package name from the directory with the darcs.cabal file) to see
what's going wrong.

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


Re: [Haskell-cafe] building darcs failed (Unable to link against the iconv library)

2013-03-03 Thread Brandon Allbery
On Sun, Mar 3, 2013 at 10:21 AM, Dmitry Malikov wrote:

> checking  whether  to  use  -liconv...  setup:  Unable  to  link  against
>  the  iconv  library.
> Failed  to  install  darcs-2.8.4
> cabal:  Error:  some  packages  failed  to  install:
>
> What is actually going on here? Iconv libraries already installed with
> libc6 package.
> Running ubuntu, cabal-install-1.16.0.2.


Linux distinguishes between runtime and linkable libraries; you probably
need to install the libc6-dev package to get the latter. (This is not a
Haskell-specific issue; configure is using a C program to test the link.)

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


Re: [Haskell-cafe] cabal install ghc-mod installs 3 years old version

2013-03-01 Thread Brandon Allbery
On Fri, Mar 1, 2013 at 12:08 PM, Albert Y. C. Lai  wrote:

> On 13-03-01 05:10 AM, Malcolm Wallace wrote:
>
>> Doesn't Cabal tend to install library packages under the .cabal folder?
>>  So blowing it away gets rid of the problematic ones.  (And everything
>> else.)
>>
>
> You need to perform scientific experiments to refute that claim, then see
> my
>

At least some versions of cabal-install do put the actual library install
trees under .cabal/lib, then register them under .ghc.

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


Re: [Haskell-cafe] Question about forkIO

2013-02-28 Thread Brandon Allbery
On Thu, Feb 28, 2013 at 6:09 AM, C K Kashyap  wrote:

> Say I have a haskell function 'f' that does a forkIO and starts an action
> "a".  I create a DLL of this haskell code and inovke "f" from C. Can I
> expect the "a" to continue to run once "f" has returned to C?
>

While you're off in C the I/O manager and garbage collector are suspended.
Many C programs are not prepared to deal with the side effects of their
operation, such as being interrupted by timer signals; moreover, it is not
possible to have multiple handlers at the OS level for a signal, and C
programs may want to use the signal handlers themselves.

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


Re: [Haskell-cafe] ANN: Nomyx 0.1 beta, the game where you can change the rules

2013-02-27 Thread Brandon Allbery
On Wed, Feb 27, 2013 at 8:37 AM, Corentin Dupont
wrote:

> Hi Chris,
> Thanks!
> That's true for the user number. What should I do? Encrypt it?


It's not that you have a user number, or even that it's accessible: it's
that it's the entirety of access control, meaning that if the user changes
it they can masquerade as another user. The correct solution is that a user
should authenticate, which creates a session hash that you stash away and
also send back to the user as a cookie so the browser will present it on
accesses. Then you check that the presented hash is there and matches the
session hash. These should expire periodically, requiring the user to log
back in again.

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


Re: [Haskell-cafe] Parser left recursion

2013-02-24 Thread Brandon Allbery
On Sun, Feb 24, 2013 at 6:31 AM, Martin Drautzburg  wrote:

> Just a silly quick question: why isn't right-recursion a similar problem?
>

Very roughly:

Left recursion is:  let foo n = n + foo n in ...
Right recursion is:  let foo 1 = 1; foo n = n + foo (n - 1) in ...

In short, matching the tokens before the right recursion will constitute an
end condition that will stop infinite recursion --- if only because you'll
hit the end of the input.   Left recursion doesn't consume anything, just
re-executes itself.

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


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

2013-02-23 Thread Brandon Allbery
On Sat, Feb 23, 2013 at 1:58 PM, C K Kashyap  wrote:

> What I am really looking for is a small sample code that demonstrates how
> TLS package can be used to connect to a webserver or imapserver.
>

TLS isn't actually SSL, despite SSL getting blessed as "TLS 0.9". Various
attempts at TLS-enabled web protocols have foundered, so you won't find
much code to speak TLS to web servers. (SSL is negotiated at socket connect
time and involves no protocol commands.) In short, sample code that can do
https would be completely useless for comparing to TLS-enabled code.

IMAP is somewhat harder than SMTP; I suggest you read up on the protocol.
I've done a fair amount of work with it, and still would have to refer to
the RFC to establish a connection without the help of an existing IMAP
library.

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


Re: [Haskell-cafe] What is a Haskell way to implement flags?

2013-02-19 Thread Brandon Allbery
On Tue, Feb 19, 2013 at 10:11 AM, Branimir Maksimovic wrote:

>  In C usual way is to set some bit in integer variable by shifting or
> oring,
> and than check flag integer variable by anding with particular flag value.
> What is Haskell way?
>

You can do that, but a somewhat more idiomatic way would be a list (or,
slightly less conveniently but more accurately, a Data.Set) of constructors
from a flags ADT.

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


Re: [Haskell-cafe] performance question

2013-02-13 Thread Brandon Allbery
On Wed, Feb 13, 2013 at 5:45 PM,  wrote:

> > On 13.02.2013 21:41, Brandon Allbery wrote:
> >> The native solution is a parser like parsec/attoparsec.
>
> "Aleksey Khudyakov"  replied
>
> > Regexps only have this problem if they are compiled from string. Nothing
> > prevents from building them using combinators. regex-applicative[1] uses
> > this approach and quite nice to use.
> >
> > [1] http://hackage.haskell.org/package/regex-applicative
>
> That _is_ a nice package, but
>   it _is_ 'a parser like parsec/attoparsec'.


Well, yes; it's a case in point.

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


Re: [Haskell-cafe] performance question

2013-02-13 Thread Brandon Allbery
On Wed, Feb 13, 2013 at 12:46 PM, David Thomas wrote:

> The fact that parsec and attoparsec exist and can be pressed into service
> with reasonable performance (I think?) on tasks for which regexps are
> suitable is probably another big part of the reason no one's done it yet.
>  I expect much of the plumbing would wind up looking a lot like those,
> actually.
>

When I started out with Haskell, one of my early thoughts was about
designing a DSL for Icon-style pattern matching; I dropped it when I
realized I was reinventing (almost identically, at least for its lower
level combinators) Parsec.  Nothing really to be gained except from a
tutelary standpoint.  And the mapping from Icon patterns to regex patterns
is pretty much mechanical if you phrase it so you aren't executing code in
the middle.

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


Re: [Haskell-cafe] performance question

2013-02-13 Thread Brandon Allbery
On Wed, Feb 13, 2013 at 11:32 AM, Nicolas Bock wrote:

> Since I have very little experience with Haskell and am not used to
> Haskell-think yet, I don't quite understand your statement that regexes are
> seen as foreign to Haskell-think. Could you elaborate? What would a more
> "native" solution look like? From what I have learned so far, it seems to
> me that Haskell is a lot about clear,
>

The native solution is a parser like parsec/attoparsec.  The problem with
regexes is that you can't at compile time verify that, for example, you
have as many matching groups in the regex as the code using it expects, nor
does an optional matching group behave as a Maybe like it should; nor are
there nice ways to recover.  A parser gives you full control and better
compile time checking, and is generally recommended.

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


Re: [Haskell-cafe] performance question

2013-02-13 Thread Brandon Allbery
On Tue, Feb 12, 2013 at 11:32 PM,  wrote:

> actualy native code compiler.  Can't regex be done effectively in haskell
> ?  Is it something that can't be done, or is it just such minimal effort to
> link to pcre that it's not worth the trouble ?
>

PCRE is pretty heavily optimized.  POSIX regex engines generally rely on
vendor regex libraries which my not be well optimized; there is a native
Haskell implementation as well, but that one runs into a different issue,
namely a lack of interest (regexes are often seen as "foreign" to
Haskell-think, so there's little interest in making them work well; people
who *do* need them for some reason usually punt to pcre).

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


Re: [Haskell-cafe] How far compilers are allowed to go with optimizations?

2013-02-09 Thread Brandon Allbery
On Sat, Feb 9, 2013 at 3:56 AM, Johan Holmquist  wrote:

> The code goes into production and, disaster. The new "improved"
> version runs 3 times slower than the old, making it practically
> unusable. The new version has to be rolled back with loss of uptime
> and functionality and  management is not happy with P.
>
> It just so happened that the old code triggered some aggressive
> optimization unbeknownst to everyone, **including the original
> developer**, while the new code did not. (This optimization maybe even
>

This leads ultimately to not allowing compilers to optimize at all.  I
suspect that's a bad plan.  Keep in mind that a modern web application may
be heavily enough used that it doesn't even need to be a
"hyper-optimization"; even small changes in performance can scale to large
performance differences.

Also... what happens when it's not just manual optimization but a bug fix
that triggers this?

Maybe this is something that would never happen in practice, but how
> to be sure...
>

If this really scares you, disable all compiler optimization.  Now you can
be sure even at large scales where even small changes can have huge
effects... and now you'd better be good at hand optimization.  And writing
code in assembly language so you can get that optimization.

This sounds like going backwards to me.

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


Re: [Haskell-cafe] How far compilers are allowed to go with optimizations?

2013-02-06 Thread Brandon Allbery
On Wed, Feb 6, 2013 at 6:45 AM, Jan Stolarek  wrote:

> nevertheless I objected to his opinion, claiming that if compiler
> performed such a high-level
> optimization - replace underlying data structure with a different one and
> turn one algorithm into
> a completely different one - programmer wouldn't be able to reason about
> space behaviour of a
> program. I concluded that such a solution should not be built into a
> compiler but instead turned
> into an EDSL.
>

For what it's worth, the main dividing line between -O1 and -O2 in gcc is
that -O2 may change space or time behavior in unexpected ways.  (This may
explain e.g.
https://plus.google.com/u/0/102208456519922110915/posts/DZsZ6mvA4T6)

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


Re: [Haskell-cafe] Next Meetup

2013-02-04 Thread Brandon Allbery
On Mon, Feb 4, 2013 at 3:53 PM, Albert Y. C. Lai  wrote:

> Toronto is an international metropolis with three globally renowned
> universities, multiple major-player high-tech labs, a world-class orchestra
> and several world-class choirs, and fine cuisines from almost all cultures.
> Toronto is home of the Toronto Haskell Meetup. The Toronto Haskell Meetup
> welcomes attendees from all over the world.
>

I'm sure, but it still helps to say *which* meetup is inviting those
attendees

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


Re: [Haskell-cafe] linking errors while compile hugs98 in macos

2013-01-31 Thread Brandon Allbery
On Thu, Jan 31, 2013 at 10:15 PM, Junior White  wrote:

> So that lua best fits the rule very well, but i like haskell much more.
> After doing some research, I find in the haskell world, there is a hugs
> fits my  demands. I'm sad to know that no one is maintaining hugs any more.
> I asking someone to keep develop on it, if no one, can I do it myself?
>

Probably you could, but the effort needed might be significant.  In
particular fixing things like environ see
https://bugs.ruby-lang.org/attachments/2591/ruby-changes.patch for the kind
of change you'll need to make, although I have to say the way they chose to
do it is risky at best (but sadly typical).  Probably something similar for
other missing symbols; feel free to ask me for help in private email.

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


  1   2   3   4   >