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

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

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

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


Re: [Haskell-cafe] Reference monad

2011-03-11 Thread Levent Erkok
On Mar 11, 2011, at 7:37 PM, Luke Palmer wrote:
> On Fri, Mar 11, 2011 at 8:18 PM, Joshua Ball  wrote:
>> Suppose I want the following functions:
>> 
>> newRef :: a -> RefMonad (Ref a)
>> readRef :: Ref a -> RefMonad a
>> writeRef :: Ref a -> a -> RefMonad ()
> 
> I would be delighted to see a pure, unsafe*-free implementation of
> your interface.  I have never seen one, and I don't really expect it
> to exist.  Likewise I would love to see a proof that it doesn't.

This message from Koen Claessen, dating back to 2001, discusses precisely this 
issue:

 http://www.mail-archive.com/haskell@haskell.org/msg09207.html

Quoting Koen:

   "I conjecture this functionality cannot be implemented in Haskell 98, nor in 
any of the known safe extensions of Haskell."

I think the folk consensus in the community is that Koen was right. While a 
proof along the lines of "doing so would violate parametricity" seems 
plausible, I can't recall anybody attempting a rigorous proof so far.

-Levent.


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


Re: [Haskell-cafe] Light and fast http server

2011-03-11 Thread Don Stewart
snap or warp/yesod. maybe in a few years we will have a winner for the
platform...

--dons

On Friday, March 11, 2011, Vo Minh Thu  wrote:
> 2011/3/11 Victor Oliveira :
>> Hi cafe,
>>
>> There are a lot of http servers in hackage. I didn't have used none.
>> I would like to know if one of them is something closer of the nginx.
>> I need some light and fast. It don't need support all http, just the basics 
>> is fine.
>> Suggestions?
>
> Snap and Warp come to mind. Have a look at this reddit thread:
> http://www.reddit.com/r/programming/comments/flpao/the_haskell_high_performance_server_shootout/
>
> Cheers,
> Thu
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

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


Re: [Haskell-cafe] Reference monad

2011-03-11 Thread Luke Palmer
On Fri, Mar 11, 2011 at 8:18 PM, Joshua Ball  wrote:
> Suppose I want the following functions:
>
> newRef :: a -> RefMonad (Ref a)
> readRef :: Ref a -> RefMonad a
> writeRef :: Ref a -> a -> RefMonad ()

Assuming this is a pure interface, you need one more thing:

runRefMonad :: RefMonad a -> a

This little function creates a lot of big issues.  For example:

foo :: (Int, ())
foo = (runRefMonad (readRef ref), comp)
where
ref = runRefMonad (newRef 42)
comp = runRefMonad (writeRef ref 32)

What is the value of foo?

This issue is solved by the type system trick of Control.Monad.ST,
which is essentially the monad you describe.  But it is not
implemented purely (even though it has a pure interface).

If you wanted to do it with a state monad and a Map, you have more
problems than just garbage collection.  You have to have a
heterogeneous map, because different references can hold values of
different types.  There are three ways I am aware of of making a
heterogeneous map:

(1) allocating unique keys (requires the map to be in a ST-like
existential context to be safe) and storing GHC.Prim.Anys in the map,
and unsafeCoercing, relying on the type system to show that the
unsafeCoerce is safe.
(2) allocating unique keys (w/existential context) and storing
Dynamics, then casting.  Requires a (Typeable a) constraint on your
operations, and is really just as unsafe as above (what do you do when
the cast fails?)
(3) keeping track of the keys in the type (a la hetero-map on
hackage).  Incompatible with the standard Monad class, which does not
allow the type to change between binds.

There may be more, of course.  But so far they all seem to involve
some sort of trickery.

I would be delighted to see a pure, unsafe*-free implementation of
your interface.  I have never seen one, and I don't really expect it
to exist.  Likewise I would love to see a proof that it doesn't.

Luke

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


[Haskell-cafe] Reference monad

2011-03-11 Thread Joshua Ball
Hi,

Suppose I want the following functions:

newRef :: a -> RefMonad (Ref a)
readRef :: Ref a -> RefMonad a
writeRef :: Ref a -> a -> RefMonad ()

for some appropriate data Ref = ...

Obviously these functions are already satisfied by IORefs and STM.

But if I wanted to implement my own (for fun)... would it be possible?
Particularly, in a pure way, without unsafePerformIO?

runRefMonad :: RefMonad a -> a

I could try to do it with a state monad, and keep all of the refs in a
Data.Map, but then I would have to solve the garbage collection
problem, so that doesn't really work.

Josh "Ua" Ball

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


[Haskell-cafe] Flexible Wrappers - an Introduction

2011-03-11 Thread Iain Alexander
There are three flexible wrappers provided in the initial flexiwrap package 
[1].  (More may be required in the future.)  

short   longwraps
FW  FlexiWrap   values
FWT FlexiWrapT  unary type constructors
FWCTC   FlexiWrapCTCbinary operators which combine two
unary type constructors

The short names are frequently convenient since type signatures can get quite 
long.  The suffixes are a simple encoding of the kind of the wrapped quantity, 
description of which I defer to a later post.  

The first parameter to each of these is a phantom - it plays no part in the 
implementation type, but serves as an index to generate multiple distinct types 
from each wrapper. In addition, by using a type-level list here, we can use it 
to specify any number of instance implementations.  

By way of a rather contrived but simple example, the module 
Data.Flex.SmallCheck.Wrap implements and uses an instance selector called 
FWEqFirst to implement an Eq instance which compares pairs by their first 
element.  It is used there by defining a type  

FW (FWEqFirst :*: TNil) (Bool, Bool)

which has the requisite properties.

The initial proof-of-concept version of the package provides only a limited 
number of instance selectors (with the associated machinery) for each wrapper.  


FW (in Data.Flex.Wrap) has only an implementation for Eq instances, with 
FWDefaultEq to explicitly specify the default implementation which simply 
delegates to the underlying wrapped type.  

FWT (Data.Flex.WrapT) has

FWTDefaultFunctor (Functor)
FWTDefaultApplicative (Applicative)
FWTDefaultMonadAll (the combination of FWTDefaultMonad and
FWTDefaultMonadState)
FWTDefaultMonad (Monad)
FWTDefaultMonadState (MonadState)

which all again delegate to the underlying type.

There is also a separate module Data.Flex.WrappedMonad which provides selectors 
to implement Functor and Applicative instances for a Monad which lacks them.  

FWWrapMonad (the combination of FWMonadFunctor and FWMonadApplicative)
FWMonadFunctor (Monad => Functor)
FWMonadApplicative (Monad => Applicative)

FWCTC (Data.Flex.WrapCTC) has

FWCTCDefaultFunctor (Functor)
FWCTCDefaultMonad (Monad)

which simply delegate to the application of the wrapped binary operator to two 
constructor arguments, but provides underlying machinery for these together 
with MonadPlus and MonadTrans.  

Data.Flex.Compose contains the (:.) (alias O) type composition operator as 
found in e.g. the TypeCompose package [2].  It contains a fairly literal 
translation of Mark Jones and Luc Duponcheel's scheme for monad composition 
[3],  

FWCompP - use the "prod" construction
FWCompD - use the "dorp" construction
FWCompS - use the "swap" construction

and selectors for MonadTrans and MonadPlus

FWCompDefaults (the combination of FWCompTrans and FWCompMonadPlus)
FWCompTrans (MonadTrans)
FWCompMonadPlus (a synonym for FWCompMonadPlusR)
FWCompMonadPlusR (using the MonadPlus instance of the right-hand
argument of the composition)
FWCompMonadPlusL (using the MonadPlus instance of the left-hand
argument of the composition)

Data.Flex.FlipT contains the operator FlipT which flips the arguments of an 
operator such as (:.).  

FWFlipDefaults (the combination of FWFlipMonad and FWFlipMonadPlus)
FWFlipMonad (Monad)
FWFlipMonadPlus (MonadPlus)

These delegate the implementation to the underlying binary operator, which it 
wraps with FWCTC, passing the phantom selector list along.  

So, to recap the example given in the package release announcement:

data FWStrict = FWStrict

type Strict = FW (FWStrict :*: TNil)

type StrictT = FWCTC
(FWFlipDefaults :*:
FWCompMonadPlusL :*: FWCompDefaults :*: FWCompS :*: TNil
)
(FlipT O) Strict

defines a (e.g. monad, but in general constructor) transformer StrictT. FWCTC 
is a flexible wrapper.  Its first parameter is an HList-like type-level list of 
instance specifications.  O is the type composition operator, and FlipT flips 
its arguments.  Strict is a user-defined wrapper type. (This is strict vs. 
loose, not strict vs. lazy.  It is intended to be used to wrap values of a data 
structure which satisfy certain criteria.) FWCompMonadPlusL specifies a 
particular MonadPlus instance (which delegates to the left operand of the 
composition, which is the right operand of the flipped composition, i.e. 
whatever argument you pass to StrictT), and FWCompS specifies the 
Jones/Duponcheel SComp construction [3].  The other two items in the list 
(apart from the TNil terminator) specify default implementations of other 
instances.  

[1] http://hackage.haskell.org/package/flexiwrap-0.0.1
[2] http://hackage.haskell.org/package/TypeCompose
[3] http://web.cecs.pdx.edu/~mpj/pubs/RR-1004.pdf


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


Re: [Haskell-cafe] Light and fast http server

2011-03-11 Thread Vo Minh Thu
2011/3/11 Victor Oliveira :
> Hi cafe,
>
> There are a lot of http servers in hackage. I didn't have used none.
> I would like to know if one of them is something closer of the nginx.
> I need some light and fast. It don't need support all http, just the basics 
> is fine.
> Suggestions?

Snap and Warp come to mind. Have a look at this reddit thread:
http://www.reddit.com/r/programming/comments/flpao/the_haskell_high_performance_server_shootout/

Cheers,
Thu

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


[Haskell-cafe] Light and fast http server

2011-03-11 Thread Victor Oliveira
Hi cafe,

There are a lot of http servers in hackage. I didn't have used none.
I would like to know if one of them is something closer of the nginx.
I need some light and fast. It don't need support all http, just the basics is 
fine.
Suggestions?

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


Re: [Haskell-cafe] Need help to solve this question

2011-03-11 Thread Brent Yorgey
http://www.haskell.org/haskellwiki/Homework_help

On Fri, Mar 11, 2011 at 09:26:59PM +, Chatura Roche wrote:
> Both sections relate to the case study: Index for a document of text.
> 
> SECTION A:
> 
> Given the attached Haskell code which produces an index of words, make the
> following alterations by modifying existing functions and including new
> functions where necessary :
> 
> 3) Treat a capitalised word (one or more capitals) as being different from
> the word in all lower case (but they should still be sorted alphabetically)
> – unless it is at the start of a sentence with only the initial letter
> capitalised. A sentence is terminated by a ‘.’, ‘?’ or ‘!’.
> 
> 
> import Prelude
> 
> type Doc = String type Line = String type Word = String
> 
> makeIndex :: Doc -> [ ([Int], Word) ]
> 
> makeIndex
> 
> = shorten . -- [([Int], Word)] -> [([Int], Word)]
> 
> amalgamate .-- [([Int], Word)] -> [([Int], Word)] makeLists . -- [(Int,
> Word)] -> [([Int], Word)] sortLs . -- [(Int, Word)] -> [(Int, Word)]
> 
> allNumWords .-- [(Int, Line)] -> [(Int, Word)] numLines . -- [Line] ->
> [(Int, Line)] splitUp -- Doc -> [Line]
> 
> splitUp :: Doc -> [Line]
> 
> splitUp [] = [] splitUp text
> 
> = takeWhile (/='\n') text : -- first line
> 
> (splitUp . -- splitup other lines
> 
> dropWhile (==’\n’) . -- delete 1st newline(s) dropWhile (/='\n')) text --
> other lines
> 
> numLines :: [Line] -> [(Int, Line)]
> 
> numLines lines -- list of pairs of
> 
> = zip [1 .. length lines] lines -- line no. & line
> 
> -- for each line -- a) split into words -- b) attach line no. to each word
> 
> splitWords :: Line -> [Word] -- a)
> 
> splitWords [] = [] splitWords line
> 
> = takeWhile isLetter line : -- first word in line
> 
> (splitWords . -- split other words
> 
> dropWhile (not.isLetter) . -- delete separators dropWhile isLetter) line --
> other words
> 
> where isLetter ch
> 
> = (‘a’<=ch) && (ch<=’z’)
> 
> (‘A’<=ch) && (ch<=’Z’)
> 
> numWords :: (Int, Line) -> [(Int, Word)] -- b)
> 
> numWords (number, line)
> 
> = map addLineNum ( splitWords line) -- all line pairs
> 
> where addLineNum word = (number, word) -- a pair
> 
> allNumWords :: [(Int, Line)] -> [(Int, Word)]
> 
> allNumWords = concat . map numWords -- doc pairs
> 
> sortLs :: [(Int, Word)] -> [(Int, Word)]
> 
> sortLs [ ] = [ ] sortLs (a:x)
> 
> = sortLs [b | b <- x, compare b a] -- sort 1st half
> 
> ++ [a] ++ -- 1st in middle sortLs [b | b <- x, compare a b] -- sort 2nd half
> 
> where compare (n1, w1) (n2, w2)
> 
> = (w1 < w2) -- 1st word less
> 
> (w1 == w2 && n1 < n2) -- check no.
> 
> makeLists :: [(Int, Word)] -> [([Int], Word)]
> 
> makeLists
> 
> = map mk -- all pairs
> 
> where mk (num, word) = ([num], word)
> 
> -- list of single no.
> 
> amalgamate :: [([Int], Word)] -> [([Int], Word)]
> 
> amalgamate [ ] = [ ] amalgamate [a] = [a] amalgamate ((n1, w1) : (n2, w2) :
> rest)-- pairs of pairs
> 
> | w1 /= w2 = (n1, w1) : amalgamate ((n2, w2) : rest) | otherwise =
> amalgamate ((n1 ++ n2, w1) : rest)
> 
> -- if words are same grow list of numbers
> 
> shorten :: [([Int], Word)] -> [([Int], Word)]
> 
> shorten
> 
> = filter long -- keep pairs >4
> 
> where
> 
> long (num, word) = length word > 4 -- check word >4

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


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


[Haskell-cafe] Need help to solve this question

2011-03-11 Thread Chatura Roche
Both sections relate to the case study: Index for a document of text.

SECTION A:

Given the attached Haskell code which produces an index of words, make the
following alterations by modifying existing functions and including new
functions where necessary :

3) Treat a capitalised word (one or more capitals) as being different from
the word in all lower case (but they should still be sorted alphabetically)
– unless it is at the start of a sentence with only the initial letter
capitalised. A sentence is terminated by a ‘.’, ‘?’ or ‘!’.


import Prelude

type Doc = String type Line = String type Word = String

makeIndex :: Doc -> [ ([Int], Word) ]

makeIndex

= shorten . -- [([Int], Word)] -> [([Int], Word)]

amalgamate .-- [([Int], Word)] -> [([Int], Word)] makeLists . -- [(Int,
Word)] -> [([Int], Word)] sortLs . -- [(Int, Word)] -> [(Int, Word)]

allNumWords .-- [(Int, Line)] -> [(Int, Word)] numLines . -- [Line] ->
[(Int, Line)] splitUp -- Doc -> [Line]

splitUp :: Doc -> [Line]

splitUp [] = [] splitUp text

= takeWhile (/='\n') text : -- first line

(splitUp . -- splitup other lines

dropWhile (==’\n’) . -- delete 1st newline(s) dropWhile (/='\n')) text --
other lines

numLines :: [Line] -> [(Int, Line)]

numLines lines -- list of pairs of

= zip [1 .. length lines] lines -- line no. & line

-- for each line -- a) split into words -- b) attach line no. to each word

splitWords :: Line -> [Word] -- a)

splitWords [] = [] splitWords line

= takeWhile isLetter line : -- first word in line

(splitWords . -- split other words

dropWhile (not.isLetter) . -- delete separators dropWhile isLetter) line --
other words

where isLetter ch

= (‘a’<=ch) && (ch<=’z’)

(‘A’<=ch) && (ch<=’Z’)

numWords :: (Int, Line) -> [(Int, Word)] -- b)

numWords (number, line)

= map addLineNum ( splitWords line) -- all line pairs

where addLineNum word = (number, word) -- a pair

allNumWords :: [(Int, Line)] -> [(Int, Word)]

allNumWords = concat . map numWords -- doc pairs

sortLs :: [(Int, Word)] -> [(Int, Word)]

sortLs [ ] = [ ] sortLs (a:x)

= sortLs [b | b <- x, compare b a] -- sort 1st half

++ [a] ++ -- 1st in middle sortLs [b | b <- x, compare a b] -- sort 2nd half

where compare (n1, w1) (n2, w2)

= (w1 < w2) -- 1st word less

(w1 == w2 && n1 < n2) -- check no.

makeLists :: [(Int, Word)] -> [([Int], Word)]

makeLists

= map mk -- all pairs

where mk (num, word) = ([num], word)

-- list of single no.

amalgamate :: [([Int], Word)] -> [([Int], Word)]

amalgamate [ ] = [ ] amalgamate [a] = [a] amalgamate ((n1, w1) : (n2, w2) :
rest)-- pairs of pairs

| w1 /= w2 = (n1, w1) : amalgamate ((n2, w2) : rest) | otherwise =
amalgamate ((n1 ++ n2, w1) : rest)

-- if words are same grow list of numbers

shorten :: [([Int], Word)] -> [([Int], Word)]

shorten

= filter long -- keep pairs >4

where

long (num, word) = length word > 4 -- check word >4
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Uncatchable error

2011-03-11 Thread Daniel Peebles
It's a hack by design, to work around libraries that do the wrong thing.

On Fri, Mar 11, 2011 at 4:07 PM, Henning Thielemann <
lemm...@henning-thielemann.de> wrote:

>
> On Fri, 11 Mar 2011, Daniel Peebles wrote:
>
>  Check out the spoon package on hackage. It's designed for these kinds of
>> situations, and
>> will wrap up common user-generated "pure" exceptions into a Maybe (and
>> will return
>> Nothing in the cases you describe)
>>
>
> This is a hack, since 'undefined' cannot be detected in general. The clean
> solution would be to find out where invalid file descriptors are detected in
> the IO code, and throw a real IOException instead of an 'error'.
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Uncatchable error

2011-03-11 Thread Henning Thielemann


On Fri, 11 Mar 2011, Daniel Peebles wrote:


Check out the spoon package on hackage. It's designed for these kinds of 
situations, and
will wrap up common user-generated "pure" exceptions into a Maybe (and will 
return
Nothing in the cases you describe)


This is a hack, since 'undefined' cannot be detected in general. The clean 
solution would be to find out where invalid file descriptors are detected 
in the IO code, and throw a real IOException instead of an 'error'.


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


Re: [Haskell-cafe] Uncatchable error

2011-03-11 Thread Daniel Peebles
Check out the spoon package on hackage. It's designed for these kinds of
situations, and will wrap up common user-generated "pure" exceptions into a
Maybe (and will return Nothing in the cases you describe)

-Dan

On Fri, Mar 11, 2011 at 11:04 AM, Daniel Díaz wrote:

> Hi, cafe,
>
> I'm working in a program where I use many connections with Network.HTTP.
> Sometimes, connections are closed while my program is reading them, and an
> error appears:
>
> : Data.ByteString.hGetLine: invalid argument (Bad file
> descriptor)
>
> All I need is to handle this error. The function 'catch' doesn't work. I
> guess this error comes from a call to 'error' function, or something
> similar.
>
> What I can do?
>
> Thanks in advance,
> Daniel Díaz
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Uncatchable error

2011-03-11 Thread Henning Thielemann


On Fri, 11 Mar 2011, Daniel Fischer wrote:


On Friday 11 March 2011 17:04:16, Daniel Díaz wrote:

Hi, cafe,

I'm working in a program where I use many connections with Network.HTTP.
Sometimes, connections are closed while my program is reading them, and
an error appears:

: Data.ByteString.hGetLine: invalid argument (Bad file
descriptor)

All I need is to handle this error. The function 'catch' doesn't work. I
guess this error comes from a call to 'error' function, or something
similar.


Control.Exception.catch can catch error calls. If you're using
Prelude.catch, you probably should switch.


Using 'error' in such cases would be definitely wrong, since a connection 
closed by the other end of the connection is not a programming error but 
an exceptional situation that we must handle properly at runtime.


Unfortunately it is not documented in bytestring package, what exceptions 
hGetLine can throw and the type IO does not tell us, too.
(For alternatives see: 
http://www.haskell.org/pipermail/haskell-cafe/2011-March/089936.html)


You may scan the exceptions in
  
http://hackage.haskell.org/packages/archive/base/4.3.1.0/doc/html/Control-Exception.html
 for types that may be responsible for invalid file descriptors. This 
should certainly be in IOException, but on the other hand, IOException is 
also what Prelude.catch catches.


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


Re: [Haskell-cafe] possible bug for ghc 7 + xcode 4 on snow leopard?

2011-03-11 Thread Carter Schonwald
fyi all: the relevant GHC ticket has already been done and the difference in
how to build the ghc pkg has been identified.

On Fri, Mar 11, 2011 at 11:39 AM, Carter Schonwald <
carter.schonw...@gmail.com> wrote:

> the latest xcode installer has no customization dialogues.
>
>
> On Fri, Mar 11, 2011 at 9:46 AM, Mark Lentczner 
> wrote:
>
>> I don't have Xcode4 (yet), but I'd be very surprised if Apple created
>> an environment that cut off development for older releases.
>>
>> In the past, the SDKs for some older releases have been an optional
>> part of the install. That is, you've had to go to the customize
>> installation screen and explicitly enable older SDKs. With the latest
>> Xcodes, for example, the SDK for 10.3 was optional. I'm a little
>> surprised that 10.5 would be put in that category... but it's
>> possible.
>>
>> Can someone with Xcode4 start the installer and go to the Customize
>> screen and see if the SDK for 10.5 is an option there? (You can do
>> this safely even if you've already installed... in fact, prior
>> installers let you install a previously not-installed component at
>> this point.)
>>
>> - Mark
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] possible bug for ghc 7 + xcode 4 on snow leopard?

2011-03-11 Thread Carter Schonwald
the latest xcode installer has no customization dialogues.

On Fri, Mar 11, 2011 at 9:46 AM, Mark Lentczner wrote:

> I don't have Xcode4 (yet), but I'd be very surprised if Apple created
> an environment that cut off development for older releases.
>
> In the past, the SDKs for some older releases have been an optional
> part of the install. That is, you've had to go to the customize
> installation screen and explicitly enable older SDKs. With the latest
> Xcodes, for example, the SDK for 10.3 was optional. I'm a little
> surprised that 10.5 would be put in that category... but it's
> possible.
>
> Can someone with Xcode4 start the installer and go to the Customize
> screen and see if the SDK for 10.5 is an option there? (You can do
> this safely even if you've already installed... in fact, prior
> installers let you install a previously not-installed component at
> this point.)
>
> - Mark
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Uncatchable error

2011-03-11 Thread Daniel Fischer
On Friday 11 March 2011 17:04:16, Daniel Díaz wrote:
> Hi, cafe,
> 
> I'm working in a program where I use many connections with Network.HTTP.
> Sometimes, connections are closed while my program is reading them, and
> an error appears:
> 
> : Data.ByteString.hGetLine: invalid argument (Bad file
> descriptor)
> 
> All I need is to handle this error. The function 'catch' doesn't work. I
> guess this error comes from a call to 'error' function, or something
> similar.

Control.Exception.catch can catch error calls. If you're using 
Prelude.catch, you probably should switch.

> 
> What I can do?
> 
> Thanks in advance,
> Daniel Díaz
> 
> 

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


Re: [Haskell-cafe] Help with how to concatenate with own datatypes

2011-03-11 Thread eldavido
Yeah, that works! Thanks! 

--
View this message in context: 
http://haskell.1045720.n5.nabble.com/Help-with-how-to-concatenate-with-own-datatypes-tp3424433p3425325.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


[Haskell-cafe] Uncatchable error

2011-03-11 Thread Daniel Díaz
Hi, cafe,

I'm working in a program where I use many connections with Network.HTTP.
Sometimes, connections are closed while my program is reading them, and an
error appears:

: Data.ByteString.hGetLine: invalid argument (Bad file
descriptor)

All I need is to handle this error. The function 'catch' doesn't work. I
guess this error comes from a call to 'error' function, or something
similar.

What I can do?

Thanks in advance,
Daniel Díaz


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


Re: [Haskell-cafe] possible bug for ghc 7 + xcode 4 on snow leopard?

2011-03-11 Thread Mark Lentczner
I don't have Xcode4 (yet), but I'd be very surprised if Apple created
an environment that cut off development for older releases.

In the past, the SDKs for some older releases have been an optional
part of the install. That is, you've had to go to the customize
installation screen and explicitly enable older SDKs. With the latest
Xcodes, for example, the SDK for 10.3 was optional. I'm a little
surprised that 10.5 would be put in that category... but it's
possible.

Can someone with Xcode4 start the installer and go to the Customize
screen and see if the SDK for 10.5 is an option there? (You can do
this safely even if you've already installed... in fact, prior
installers let you install a previously not-installed component at
this point.)

- Mark

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


[Haskell-cafe] Some quick experiments with GHC 7.0.2 in Intel's Manycore Testing Lab (32 cores)

2011-03-11 Thread José Pedro Magalhães
Hi all,

I've played a bit with Intel's Manycore Testing Lab (
http://software.intel.com/en-us/articles/intel-many-core-testing-lab/). Part
of the agreement to use it requires that you report back your experiences,
which I did in an Intel forum post (
http://software.intel.com/en-us/forums/showthread.php?t=81396). I thought
this could be interesting to the Haskell community in general as well, so
I'm reposting here, and pasting the text below for convenience. I've
replaced the images with links.


Cheers,
Pedro

As per the agreement with Intel, I am reporting my experiences with the
> Intel Manycore Testing Lab (Linux). This was my first time in the lab, and I
> wanted to test GHC's [1] SMP parallelism [2] features.
>
> The first challenge was to actually get GHC to work on the lab. There was a
> working version of ghc under /opt/ghc6.13/bin/ghc, but I really needed GHC
> 7. So first I built GHC 7.0.2-rc2, which worked without much trouble.
>
> Next step was to get all the necessary libraries in place. Since the lab
> has no direct internet access, cabal-install [3] wouldn't be of much use.
> Instead, I downloaded a snapshot of hackage [4] with the latest version of
> every package and manually installed the packages I needed. A bit boring,
> but doable.
>
> Finally I was ready to compile my programs and test. First thing I tried
> was an existing algorithm I had which, at some point, takes a list of about
> 500 trees and, for each tree, computes a measure which is expressed as a
> floating point number. This is basically a map over a list transforming each
> tree into a float. Each operation is independent of the others, and all
> require the same input, so it seems ideal for parallelisation. A quick
> benchmark revealed the following running times:
>
> http://dreixel.net/images/perm/ParList.png
>
> (Note the non-linear number of cores at the end of the x-axis.) Apparently
> there are performance gains with up to 6 cores; adding more cores after this
> makes the total running time worse.
>
> While this might sound bad, do note that all that was necessary to
> parallelise this algorithm was a one line change: basically, at the point
> where the list of floats @l@ is generated, it is replaced with @l `using`
> parList rdeepseq@. This change, together with recompilation using
> -threaded, is all that is necessary to parallelise this program.
>
> Later I performed a more accurate benchmark, this time using the equality
> function (take two elements and compare them for equality). The first step
> was to parallelise the equality function, which, again, is a very simple
> task:
>
> -- Tree datatype
> data Tree a = Leaf | Bin a (Tree a) (Tree a)
>
> -- Parallel equality
> eqTreePar :: Tree Int -> Tree Int -> Bool
> eqTreePar Leaf Leaf = True
> eqTreePar (Bin x1 l1 r1) (Bin x2 l2 r2) = x1 == x2 && par l (pseq r (l &&
> r))
> where l = eqTreePar l1 l2
>   r = eqTreePar r1 r2
> eqTreePar _ _ = False
>
> `par` and `pseq` are the two primitives for parallelisation in GHC [5]. The
> performance graph follows:
>
> http://dreixel.net/images/perm/ParEq.png
>
> (This time I ran the benchmark several times; the error bars on the graph
> are the standard deviations.) Again we get performance improvements with up
> to 6 cores, and after that performance decreases. What I find really nice is
> the improvement with two cores, which is almost a 50% decrease in running
> time. The ratios for 2 to 4 cores wrt. the running time with 1 core are
> 0.52, 0.39, and 0.35, respectively. This is really good for such a simple
> change in the source code, and most people only have up to 4 cores anyway.
> In any case, the results of this (very preliminary) experiment seem to
> indicate that GHC's SMP parallelism is not particularly optimized for a high
> number of cores (yet).
>
> I'm planning to explore this line of research further, and I'm hoping to be
> able to conduct more experiments in the near future. Feel free to contact me
> if you want more information on what I've done.
>
>
> Cheers,
> Pedro
>
> [1] http://www.haskell.org/ghc/
> [2] http://www.haskell.org/ghc/docs/latest/html/users_guide/using-smp.html
> [3] http://hackage.haskell.org/package/cabal-install
> [4] http://hackage.haskell.org
> [5]
> http://hackage.haskell.org/packages/archive/parallel/latest/doc/html/Control-Parallel.html
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.ByteString.Lazy.ByteString vs Data.ByteString.Lazy.Internal.ByteString

2011-03-11 Thread Brandon Moore
It is a goal of the ByteString library that you should almost never need to work
directly with the PS constructor and the things used in that definition. If you 
find
some task involving IO or string manipulation that seems to require using the
internal operations, it's probably worth bringing it up on the list. That said,
it's always good to know how things work, and the internals may be relevant if 
you
want to make an interface to a foreign library use ByteStrings.

Look at the Foreign.* modules to see how to work with Ptr values, especially
Foreign.ForeignPtr, Foreign.Ptr, Foreign.Marshal:

http://www.haskell.org/ghc/docs/latest/html/libraries/base-4.3.1.0/Foreign-ForeignPtr.html

http://www.haskell.org/ghc/docs/latest/html/libraries/base-4.3.1.0/Foreign-Ptr.html

http://www.haskell.org/ghc/docs/latest/html/libraries/base-4.3.1.0/Foreign-Marshal.html


The GHC manual has a little bit on unboxed types like Int#

http://www.haskell.org/ghc/docs/latest/html/users_guide/primitives.html

GHC.Prim provides the basic operations

http://www.haskell.org/ghc/docs/latest/html/libraries/ghc-prim-0.2.0.0/GHC-Prim.html


There is also the original paper (from Simon Peyton-Jones' page)

http://research.microsoft.com/en-us/um/people/simonpj/papers/unboxed-values.ps.Z

Brandon



  

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


Re: [Haskell-cafe] ContT and ST stack

2011-03-11 Thread Bas van Dijk
On 11 March 2011 12:04, Bas van Dijk  wrote:
> Unfortunately foo still doesn't type check in 7.0.2:
>
> foo :: (forall s. ST s a) -> a
> foo st = ($) runST st

Note that the following does type check with ImpredicativeTypes:

bar = id runST

Bas

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


Re: [Haskell-cafe] ContT and ST stack

2011-03-11 Thread Bas van Dijk
On 11 March 2011 11:15, Max Bolingbroke  wrote:
> On 10 March 2011 17:55, Bas van Dijk  wrote:
>> On 10 March 2011 18:24, Yves Parès  wrote:
>>> Why has the operator (.) troubles with a type like (forall s. ST s a)?
>>>
>>> Why can't it match the type 'b' in (.) definition?
>>
>> As explained by the email from SPJ that I linked to, instantiating a
>> type variable (like 'b') with a polymorphic type (like 'forall s. ST s
>> a' ) is called impredicative polymorphism. Since GHC-7 this is not
>> supported any more because it was to complicated.
>
> AFAIK this decision was reversed because SPJ found a simple way to
> support them. Indeed, they work fine in 7.0.2 and generate warnings.
> Try it out:

Great!

Unfortunately foo still doesn't type check in 7.0.2:

foo :: (forall s. ST s a) -> a
foo st = ($) runST st

For the same reason I still need this ugly hack in usb-safe:

http://hackage.haskell.org/packages/archive/usb-safe/0.12/doc/html/src/System-USB-Safe.html#withDeviceWhich

Bas

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


Re: [Haskell-cafe] ContT and ST stack

2011-03-11 Thread Edward Z. Yang
Excerpts from Max Bolingbroke's message of Fri Mar 11 05:15:34 -0500 2011:
> AFAIK this decision was reversed because SPJ found a simple way to
> support them. Indeed, they work fine in 7.0.2 and generate warnings.

Correct. About a week-ish ago I submitted a patch to update the docs.

Cheers,
Edward

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


Re: [Haskell-cafe] ContT and ST stack

2011-03-11 Thread Max Bolingbroke
On 10 March 2011 17:55, Bas van Dijk  wrote:
> On 10 March 2011 18:24, Yves Parès  wrote:
>> Why has the operator (.) troubles with a type like (forall s. ST s a)?
>>
>> Why can't it match the type 'b' in (.) definition?
>
> As explained by the email from SPJ that I linked to, instantiating a
> type variable (like 'b') with a polymorphic type (like 'forall s. ST s
> a' ) is called impredicative polymorphism. Since GHC-7 this is not
> supported any more because it was to complicated.

AFAIK this decision was reversed because SPJ found a simple way to
support them. Indeed, they work fine in 7.0.2 and generate warnings.
Try it out:

{{{
{-# LANGUAGE ImpredicativeTypes #-}
module Impred where

f :: Maybe (forall a. [a] -> [a]) -> Maybe ([Int], [Char])
f (Just g) = Just (g [3], g "hello")
f Nothing  = Nothing
}}}

Unfortunately, the latest user guide still reflects the old situation:
http://www.haskell.org/ghc/docs/latest/html/users_guide/other-type-extensions.html

Cheers,
Max

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


Re: [Haskell-cafe] Convert a function to a string of operators?

2011-03-11 Thread Erik Hesselink
On Thu, Mar 10, 2011 at 13:34, Lyndon Maydwell  wrote:
>> Will methods explained here work for boolean expressions?
>
> The convenience of defining using specialised datatypes for
> serialising numeric operations comes from Num being a typeclass. This
> is not the case for Bool:
>
> Prelude> :info Num
> class (Eq a, Show a) => Num a where
>  (+) :: a -> a -> a
>   ... -- Defined in GHC.Num
>
> Prelude> :info Bool
> data Bool = False | True        -- Defined in GHC.Bool

If you want something like this for Bool (and other standard data
types) have a look at the Awesome Prelude [1]. It is an implementation
of the prelude where each data type is a type class.

Erik

[1] http://tom.lokhorst.eu/2010/02/awesomeprelude-presentation-video

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


Re: [Haskell-cafe] possible bug for ghc 7 + xcode 4 on snow leopard?

2011-03-11 Thread Jurriën Stutterheim
There is no guarantee that /Developer-old/ is still on the system, so depending 
on it for symlinking is probably not a good idea. So far I have had no problems 
symlinking /Developer/SDKs/MacOSX10.6.sdk to /Developer/SDKs/MacOSX10.5.sdk. 
This could be one alternative. However, separate Snow Leopard builds would be 
preferable, since they would not depend on a workaround to function.

Jurriën

On 11 Mar, 2011, at 10:00 , steffen wrote:

> ok, now I've installed XCode 4 and run into the very same problems.
> 
> As already said, XCode 4 targets snow leopard only. That's why the 
> MacOSX10.5.sdk is missing. unfortunately the ghc packages for snow leopard 
> are configured to support leopard still.
> 
> See: 
> /Library/Frameworks/GHC.framework/Versions/Current/usr/share/doc/ghc/html/libraries/ghc-7.0.2/src/Config.html
> 
> So we either have to copy or symling /Developer-old/SDKs/MacOSX10.5.sdk to 
> /Developer/SDKs or someone is going to recompile ghc with snow leopard only 
> in mind.
> 
> - Steffen
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe


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


Re: [Haskell-cafe] possible bug for ghc 7 + xcode 4 on snow leopard?

2011-03-11 Thread steffen
ok, now I've installed XCode 4 and run into the very same problems.

As already said, XCode 4 targets snow leopard only. That's why the 
MacOSX10.5.sdk is missing. unfortunately the ghc packages for snow leopard 
are configured to support leopard still.

See: 
/Library/Frameworks/GHC.framework/Versions/Current/usr/share/doc/ghc/html/libraries/ghc-7.0.2/src/Config.html

So we either have to copy or symling /Developer-old/SDKs/MacOSX10.5.sdk to 
/Developer/SDKs or someone is going to recompile ghc with snow leopard only 
in mind.

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


Re: [Haskell-cafe] Data.ByteString.Lazy.ByteString vs Data.ByteString.Lazy.Internal.ByteString

2011-03-11 Thread C K Kashyap
Hi Don,
What would be a good way to figure out the usage of ByteString -
particularly the PS constructor.
Regards,
Kashyap

On Fri, Feb 11, 2011 at 10:01 AM, C K Kashyap  wrote:

>
>> Yep, the 'Internal' module is where the type is defined, and then
>> re-exported through the regular module.
>>
>> Thanks Don ... good to know.
> Regards,
> Kashyap
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe