Re: [Haskell-cafe] Getting highest sum of list elements with Map

2009-08-05 Thread Gwern Branwen
-- based on http://jtauber.com/blog/2008/02/10/a_new_kind_of_graded_reader/
-- TODO: read knownwords from file
--   print out matching sentences as well (make optional)
--   fix performance; goal: handle Frank Herbert corpus in under 5 minutes

import Data.Ord
import Data.Char (isPunctuation, toLower)
import Data.List -- (nub, sort)
import qualified Data.Set as Set
import qualified Data.Map as Map
import Control.Parallel.Strategies
import Data.Function (on)

import Data.List.Split (splitWhen)

import System.IO.UTF8 (getContents, putStrLn)
import System.Environment (getArgs)

main :: IO ()
main = do depth <- fmap (read . head) $ getArgs
  corpus <- System.IO.UTF8.getContents
  let pcorpus = processCorpus corpus
  let knownwords = map (map toLower) ["You", "dont", "see", "more", "than", "that", "The", "first", "episode", "of", "Kare", "Kano", "is", "rotten", "with", "Evangelion", "visual", "motifs", "the", "trains", "the", "spotlights", "and", "telephone", "poles", "and", "wires", "the", "masks", "and", "this", "is", "how", "everyone", "sees", "me", "etc", "a", "it", "did", "are", "to", "in", "I", "Dune", "was", "Stalin", "Mussolini", "Hitler", "Churchill", "beginning", "That", "all", "be", "like", "on", "an", "Its", "But", "only", "you", "themes", "into", "as", "my", "human", "paradox","he","said","paul","his","she","her","not","him","had","for","at","alia","no","from","what","asked","they","there","have","stilgar"]
  let optimalwords = answer depth pcorpus knownwords
  System.IO.UTF8.putStrLn optimalwords

-- | Clean up. Don't want 'Je suis." to look different from "Je suis"...
--
-- > stringPunctuation "Greetings, fellow human flesh-sacks!" ~> "Greetings fellow human fleshsacks"
stripPunctuation :: String -> String
stripPunctuation = filter (not . isPunctuation)

-- Turn a single big document into a stream of sentences of individual words; lower-case so we don't get
-- multiple hits for 'He', 'he' etc
processCorpus :: String -> [[String]]
processCorpus = map (sort . words . stripPunctuation) . splitWhen (=='.') . map toLower

sentences :: (NFData a, Ord a) => [[a]] -> Map.Map Int (Set.Set a)
sentences = Map.fromList . zip [(0::Int)..] . map Set.fromList

fidiv :: (Integral a, Fractional b) => a -> a -> b
fidiv = (/) `on` fromIntegral

ranks :: (NFData v, Ord k, Ord v) => Map.Map k (Set.Set v) -> [(v, Rational)]
ranks s = Map.toList .
  Map.fromListWith (+) $
  [(word, rank) |
   (_sentenceId, wrds) <- Map.toList s,
   let rank = 1 `fidiv` Set.size wrds,
   word <- Set.toList wrds]

approximation :: (NFData v, Ord k, Ord v) => Map.Map k (Set.Set v) -> Int -> [v]
approximation _ 0 = []
approximation s n =
case ranks s of
  [] -> []
  xs -> let word = fst . maximumBy (comparing snd) $ xs in
let withoutWord = Map.map (Set.delete word) s
in word : approximation withoutWord (n-1)

process :: (Ord v, NFData v) => [[v]] -> [Int] -> [[v]]
process ss ns = map (approximation $ sentences ss) ns

getBest :: [Int] ->[[String]] -> String
getBest x y = unlines . last  $ process y x

filterKnown :: [String] -> [[String]] -> [[String]]
filterKnown known = filter (not . null) . map (filter (flip notElem $ known))

answer :: Int -> [[String]] -> [String] -> String
answer depth corp known = let corp' = filterKnown known corp in getBest  [1..depth] corp'___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: SQL Database in Haskell?

2009-08-05 Thread Max Desyatov
As I can say from my experience of usage of hdbc-sqlite3 and
happstack-state, the latter covers everything you ever wanted from
sqlite3 and more.  It you aren't too concerned about performance, you
can free yourself from many tedious routines that are imminent when you
work with relational database.  Elaborated data model design coupled
with some generics technique (uniplate with derive, e.g.) gives you a
possibility to write down your domain problem directly to haskell.

CK Kashyap  writes:

> I'd be very interested to see a rdbms implementation in Haskell ...
> perhaps a port of sqlite
>
> Regards,
> Kashyap
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: SQL Database in Haskell?

2009-08-05 Thread CK Kashyap
I'd be very interested to see a rdbms implementation in Haskell ... perhaps a 
port of sqlite

Regards,
Kashyap




From: Don Stewart 
To: Günther Schmidt 
Cc: haskell-cafe@haskell.org
Sent: Thursday, August 6, 2009 6:07:48 AM
Subject: Re: [Haskell-cafe] Re: SQL Database in Haskell?

gue.schmidt:
> Hi,
>
> well I tried to do some stuff in memory, and the app ended up using a  
> couple of gigs. I not only have a very large amount of dynamic data, CSV  
> files, but also quite a large amount of static data, and wasted 3 months  
> trying to do this all in-memory. The problem was finally solved once I  
> used SQLite and SQL.
>
> The other day I had one last go at trying to compile the static data in a 
> literal list in my haskell code. That was 80.000 rows, it was just not  
> even possible

Don't compile in static data (or if you do, use -Onot, so that GHC won't
try to analyze it)!

Use some kind of binary on-disk storage.

> As far as I'm concerned this discussion is settled in favor of SQL once  
> and for all.
>
> The part I didn't like about SQLite is encryption, you need to buy that  
> extra and then hope that it fits the current version and future ones too. 
> HSQLDB or Derby for Java give you this option and also with in-memory  
> database, alas they are for Java only.

You might also want to look at the HAppS disk-backed persistence model,

http://hackage.haskell.org/package/HAppS-State

Or the holumbus distributed storage layer,

http://hackage.haskell.org/package/Holumbus-Storage
___
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] A mistake in haskellwiki

2009-08-05 Thread Don Stewart
leaveye.guo:
> Hi haskellers:
> 
> There is a mistake in http://www.haskell.org/haskellwiki/State_Monad
> 
> It post two functions like this :
> 
>   evalState :: State s a -> s -> a
>   evalState act = fst $ runState act
> 
>   execState :: State s a -> s -> s
>   execState act = snd $ runState act
> 
> Both the '$' operators should be '.'.
> 
> Anyone would correct it ?


Well, it's a wiki ... :-)

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


[Haskell-cafe] A mistake in haskellwiki

2009-08-05 Thread L.Guo
Hi haskellers:

There is a mistake in http://www.haskell.org/haskellwiki/State_Monad

It post two functions like this :

  evalState :: State s a -> s -> a
  evalState act = fst $ runState act

  execState :: State s a -> s -> s
  execState act = snd $ runState act

Both the '$' operators should be '.'.

Anyone would correct it ?

Regards
--
L.Guo
2009-08-06

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


[Haskell-cafe] Do you understand posix well?

2009-08-05 Thread Maurí­cio CA

I've beeing writing a low-level binding to posix that can be
usefull if you want to use posix but has no time to learn FFI:

http://hackage.haskell.org/package/bindings-posix

However, my understandment of posix is barely nothing, and I see
that many of its functionality is enabled or disabled by macros,
and I don't know which ones are related to what functionality.

So, if you know about that: would you be able to list all macros
(or at least most important ones, if there are too many) that
enable all (or most) of posix? In exchange, you get a posix
binding that is actually comprehensive :)

Thanks,
Maurício

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


[Haskell-cafe] Re: Space for commentaries on hackage

2009-08-05 Thread Maurí­cio CA

>> Sure! Replace "anonymous" for "easy to write". [...]

> [...] every package I upload to hackage includes my email
> address in the "maintainer" field, and I love getting emails
> from people who use anything I maintain (even if they're asking
> me to do work! I may not do it, but it's nice to know that
> people care).

My motivation for this post is that I'm also interested on the
comments from those who don't :)

Seriously, it may be usefull to get comments like "why would I
use this, if package X already do that better?" But, for politeness
if for no other reason, people won't write you to say that.

Best,
Maurício

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


[Haskell-cafe] Re: About the import module

2009-08-05 Thread Günther Schmidt

Hi all,

I appreciate all the suggestions but I'd like to stress that in this  
particular case, the app I'm developing, SQL has proven to be the ideal  
solution, the input data is table based, I need to group, find maxes, do  
joins, whathaveyou. SQLite did miracles to memory problems and performance  
and HaskellDB made it a breeze to generate the proper SQL.


Back to my original question, is there an SQL RDBM system written in  
Haskell, for use disk- or memory based?


Günther



Am 05.08.2009, 20:04 Uhr, schrieb xu zhang :


Hi there,

If I import a module and do not explicitly point out the entities I have
imported. And I want the ghc to point out the entities automatically. Is
there any method to do this? any methods to have the ghc point out the
entities I import and export?
Because there are so many files and I don't want to change them one by  
one,

so I just want to find if there is a simple and automatic way to have the
entities pointed out.

Thank you in advance!



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


Re: [Haskell-cafe] Re: SQL Database in Haskell?

2009-08-05 Thread Don Stewart
gue.schmidt:
> Hi,
>
> well I tried to do some stuff in memory, and the app ended up using a  
> couple of gigs. I not only have a very large amount of dynamic data, CSV  
> files, but also quite a large amount of static data, and wasted 3 months  
> trying to do this all in-memory. The problem was finally solved once I  
> used SQLite and SQL.
>
> The other day I had one last go at trying to compile the static data in a 
> literal list in my haskell code. That was 80.000 rows, it was just not  
> even possible

Don't compile in static data (or if you do, use -Onot, so that GHC won't
try to analyze it)!

Use some kind of binary on-disk storage.

> As far as I'm concerned this discussion is settled in favor of SQL once  
> and for all.
>
> The part I didn't like about SQLite is encryption, you need to buy that  
> extra and then hope that it fits the current version and future ones too. 
> HSQLDB or Derby for Java give you this option and also with in-memory  
> database, alas they are for Java only.

You might also want to look at the HAppS disk-backed persistence model,

http://hackage.haskell.org/package/HAppS-State

Or the holumbus distributed storage layer,

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


[Haskell-cafe] Re: SQL Database in Haskell?

2009-08-05 Thread Günther Schmidt

Hi,

well I tried to do some stuff in memory, and the app ended up using a  
couple of gigs. I not only have a very large amount of dynamic data, CSV  
files, but also quite a large amount of static data, and wasted 3 months  
trying to do this all in-memory. The problem was finally solved once I  
used SQLite and SQL.


The other day I had one last go at trying to compile the static data in a  
literal list in my haskell code. That was 80.000 rows, it was just not  
even possible


As far as I'm concerned this discussion is settled in favor of SQL once  
and for all.


The part I didn't like about SQLite is encryption, you need to buy that  
extra and then hope that it fits the current version and future ones too.  
HSQLDB or Derby for Java give you this option and also with in-memory  
database, alas they are for Java only.


Günther


Am 06.08.2009, 02:16 Uhr, schrieb Mattias Bengtsson  
:



On Thu, 2009-08-06 at 00:04 +0200, Günther Schmidt wrote:

Hi Don,

I actually meant an SQL database written in Haskell, same as Derby or
HSQLDB in Java.

I'm currently using Sqlite3 with HDBC but would prefer one entirely in
Haskell (but still SQL though, because of persistence and performance).


SQL is just a query language and the use of it is, as far as i can tell,
orthogonal to the need for persistence and performance.



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


Re: [Haskell-cafe] SQL Database in Haskell?

2009-08-05 Thread Don Stewart
moonlite:
> On Thu, 2009-08-06 at 00:04 +0200, Günther Schmidt wrote:
> > Hi Don,
> > 
> > I actually meant an SQL database written in Haskell, same as Derby or  
> > HSQLDB in Java.
> > 
> > I'm currently using Sqlite3 with HDBC but would prefer one entirely in  
> > Haskell (but still SQL though, because of persistence and performance).
> 
> SQL is just a query language and the use of it is, as far as i can tell,
> orthogonal to the need for persistence and performance. 
> 

For pure Haskell persistance, there is

TCache: A Transactional data cache with configurable persistence
http://hackage.haskell.org/package/TCache

io-storage: A key-value store in the IO monad.
http://hackage.haskell.org/package/io-storage

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


Re: [Haskell-cafe] SQL Database in Haskell?

2009-08-05 Thread Mattias Bengtsson
On Thu, 2009-08-06 at 00:04 +0200, Günther Schmidt wrote:
> Hi Don,
> 
> I actually meant an SQL database written in Haskell, same as Derby or  
> HSQLDB in Java.
> 
> I'm currently using Sqlite3 with HDBC but would prefer one entirely in  
> Haskell (but still SQL though, because of persistence and performance).

SQL is just a query language and the use of it is, as far as i can tell,
orthogonal to the need for persistence and performance. 

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


Re: [Haskell-cafe] Haskell2Xml

2009-08-05 Thread Keith Sheppard
Hello Dmitry,

I too was looking for something like this and came up empty. I
proposed something similar on the haskell_proposals reddit...

http://www.reddit.com/r/haskell_proposals/comments/8zhkx/haxb_and_haxws/

... but I was left with the impression that there isn't much interest.

-Keith

On Wed, Aug 5, 2009 at 3:49 PM, Dmitry Olshansky wrote:
> Hello all,
> I need a convenient tool to generate Haskell types from XML W3C Schema
> Definition (xsd) and vice versa - generate instances for Haskell ADT's to
> make corresponding XML.
> It is just the same that HaXml do with DTD.
> I need
> - using XSD
> - support for unicode
> - using xml-attributes as far as elements are very desirable
> - by my opinion TemplateHaskell for generate instances is prefferable than
> using DrIFT (which used in HaXml) - both possibilities is great of course
> - generation of xsd by Haskell type is a good feature also
> and so on...
> Does this tool exist?
> Do some articles / thoughts / standards / recomendations about
> correspondence between XML and Haskell ADT's exist?
> Best wishes,
> Dmitry
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>



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


Re: [Haskell-cafe] Efficient functional idiom for histogram

2009-08-05 Thread wren ng thornton

Paul Moore wrote:

2009/8/5 Yitzchak Gale :

Or is this with an alternate RNG? Although I think even that
would be fair, since Python uses Mersenne.


I got the impression Dmitry was using Haskell's standard RNG, not
Mersenne Twister. If so, then we'd get further improvements with MT,
but that's still a hit against Haskell, as I'd interpret it as meaning
that Haskell supplies as default a PRNG which costs noticeable
performance in order to provide guarantees that "ordinary" programs
don't need.


I'm not sure how fair that is. For most "ordinary" programs I've written 
that use randomness anywhere, they have many different places that want 
randomness. Having a single global seed can suffice for this, but it 
introduces severe constraints that are seldom noticed.


Namely, these are in fact *P*RNGs. If every place needing randomness is 
given its own seed, then it becomes possible to store all those seeds, 
allowing for replay. Replay can be good for capturing the history of a 
particular run of a simulation/game ---which is difficult at best in 
non-Haskell approaches. And more critically the seeds can be stored in a 
"core dump" allowing replay as a debugging tool, allowing reproduction 
of 'random' bugs which are otherwise quite difficult to track down.


Imperative languages could use the same algorithms as Haskell, but they 
do not; which means these benefits of PRNGs are seldom even thought of. 
By separating concerns, the Haskell approach not only leads to cleaner 
code, but that separation can also be used to add new capabilities. The 
invisible manacles of imperativism should not be looked upon lightly.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Space for commentaries on hackage

2009-08-05 Thread Antoine Latter
2009/8/5 Maurí­cio CA :
>
> Sure! Replace "anonymous" for "easy to write". Although,
> thinking better, this should be something to ask at repository
> hosters, not at hackage.
>

If we're getting rid of the anonymous requirement - every package I
upload to hackage includes my email address in the "maintainer" field,
and I love getting emails from people who use anything I maintain
(even if they're asking me to do work! I may not do it, but it's nice
to know that people care).

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


Re: [Haskell-cafe] Parsec: using two different parser for the same string

2009-08-05 Thread Dan Weston
Of course, since ParsecT s u m is a functor, feel free to use fmap 
instead of parsecMap. Then you don't need to import from Text.Parsec.Prim.
And in hindsight, I might prefer the name (<:>) or cons to (<>) for the 
first function, but now I'm just obsessing. :)


Dan

Dan Weston wrote:

I think parsecMap does the job here:

---
import Text.ParserCombinators.Parsec hiding ((<|>))
import Text.Parsec.Prim(parsecMap)
import Control.Applicative((<|>))
import Control.Arrow((|||),(&&&))

-- Tagged (:)
(<>) :: Either Char Char -> Either String String -> Either String String
Left  a <> Left  b = Left  (a:b)
Left  a <> Right b = Left  (a:b)
Right a <> Left  b = Left  (a:b)
Right a <> Right b = Right (a:b)

-- Tagged concat
stringParser :: [Either Char Char] -> Either String String
stringParser = foldr (<>) (Right "")

-- Parse Integer if properly tagged, keeping unparsed string
maybeToInteger :: Either String String -> (Maybe Integer, String)
maybeToInteger = (const Nothing ||| Just . read) &&& (id ||| id)

-- Tagged-choice parser
intOrStringParser = parsecMap (maybeToInteger . stringParser)
   $ many1 (parsecMap Right digit <|> parsecMap Left (noneOf ";)"))

-- Parse between parentheses
intOrStringListParser = between (char '(')
 (char ')')
 (sepBy1 intOrStringParser (char ';'))
---

Then you get a tagged version of each string, along with the string itself:

*P> parseTest intOrStringListParser $ "(1;2w4;8;85)"
[(Just 1,"1"),(Nothing,"2w4"),(Just 8,"8"),(Just 85,"85")]

There may be some parsecMap-fold fusion optimization possible, though I 
haven't looked into that.


Dan

Paul Sujkov wrote:

Hi everybody,

suppose I have two different parsers: one just reads the string, and 
another one parses some values from it. E.g.:


parseIntList :: Parser [Integer]
parseIntList = do
  char '('
  res <- liftM (map read) (sepBy1 (many1 digit) (char ';'))
  char ')'
  return res

parseIntString :: Parser String
parseIntString = manyTill anyChar eof

so for some input like this - "(1;2;3;4)" - I will have two different 
result:


*Parlog> parseTest parseIntList "(1;2;3;4)"
[1,2,3,4]
*Parlog> parseTest parseIntString "(1;2;3;4)"
"(1;2;3;4)"

but the thing that I actually want is something like Parser ([Integer], 
String) - results from both parsers at a time, no matter whether one of 
them fails or not:


*Parlog> parseTest parseIntListAndString "(1;2;3;4)"
([1,2,3,4], "(1;2;3;4)")

it is impossible at first sight, because first parser to use will 
consume all the input, and there will be nothing to parse for the second one


Parsec contains "choice" function, but it is implemented via <|> and 
that is mplus - so it tries second alternative only if the first one 
fails. Is it possible to use two parsers for the same string (with 
try-like backtracking, no input actually consumed till the second parser 
finishes)? I can assume only dirty hacks with the GenParser internals - 
manual position storing and backtracking - but that is obviously not good


however, my first attempt to solve the problem was kind a like that: to 
parse string to String, and then to use it as an input for the next 
level parse call:


parseIntListAndString :: Parser ([Integer], String)
parseIntListAndString = do
  str <- parseIntString
  return (res str, str)
  where res str = case (parse parseIntList "" str) of
Left  err -> []
Right val -> val

but the problems with such a method began when I switched from Parser to 
GenParser with user state: function parseIntList have to update the 
state, but it can't have the same state as the parseIntListAndString any 
more: it has it's own. I can explicitly pass the state from 
parseIntListAndString to parseIntList, but I see no suitable way for the 
parseIntList to update it. I can return the updated state value from the 
parseIntList function, and call setState on a result - but it seems 
rather ugly to mee. However, if nothing else will do, that is an alternative


it is of course possible to use two different parsers sequentially, but 
it is also very ineffective: I need to use such multiple parsing on a 
relatively small substring of the actual input, so little backtracking 
would be a much nicier approach. Any suggestions?


--
Regards, Paul Sujkov





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


[Haskell-cafe] Re: Space for commentaries on hackage

2009-08-05 Thread Maurí­cio CA

It would be nice to have a place for anonimous



In these days of web spam, anonymous is not such a good idea.



Sure! Replace "anonymous" for "easy to write". Although,
thinking better, this should be something to ask at repository
hosters, not at hackage.

Best,
Maurício

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


Re: [Haskell-cafe] Space for commentaries on hackage

2009-08-05 Thread Brandon S. Allbery KF8NH

On Aug 5, 2009, at 14:37 , Maurí cio CA wrote:

It would be nice to have a place for anonimous



In these days of web spam, anonymous is not such a good idea.

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




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


Re: [Haskell-cafe] SQL Database in Haskell?

2009-08-05 Thread Günther Schmidt

Hi Don,

I actually meant an SQL database written in Haskell, same as Derby or  
HSQLDB in Java.


I'm currently using Sqlite3 with HDBC but would prefer one entirely in  
Haskell (but still SQL though, because of persistence and performance).


Günther

Am 05.08.2009, 22:32 Uhr, schrieb Don Stewart :


gue.schmidt:

Hi all,

is there an SQL Database in Haskell or is there a project trying to
implement one?



There are several bindings,

http://hackage.haskell.org/packages/archive/pkg-list.html#cat:database

Are you asking for an implementation of SQL though?

-- Don



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


Re: [Haskell-cafe] Parsec: using two different parser for the same string

2009-08-05 Thread Dan Weston

I think parsecMap does the job here:

---
import Text.ParserCombinators.Parsec hiding ((<|>))
import Text.Parsec.Prim(parsecMap)
import Control.Applicative((<|>))
import Control.Arrow((|||),(&&&))

-- Tagged (:)
(<>) :: Either Char Char -> Either String String -> Either String String
Left  a <> Left  b = Left  (a:b)
Left  a <> Right b = Left  (a:b)
Right a <> Left  b = Left  (a:b)
Right a <> Right b = Right (a:b)

-- Tagged concat
stringParser :: [Either Char Char] -> Either String String
stringParser = foldr (<>) (Right "")

-- Parse Integer if properly tagged, keeping unparsed string
maybeToInteger :: Either String String -> (Maybe Integer, String)
maybeToInteger = (const Nothing ||| Just . read) &&& (id ||| id)

-- Tagged-choice parser
intOrStringParser = parsecMap (maybeToInteger . stringParser)
  $ many1 (parsecMap Right digit <|> parsecMap Left (noneOf ";)"))

-- Parse between parentheses
intOrStringListParser = between (char '(')
(char ')')
(sepBy1 intOrStringParser (char ';'))
---

Then you get a tagged version of each string, along with the string itself:

*P> parseTest intOrStringListParser $ "(1;2w4;8;85)"
[(Just 1,"1"),(Nothing,"2w4"),(Just 8,"8"),(Just 85,"85")]

There may be some parsecMap-fold fusion optimization possible, though I 
haven't looked into that.


Dan

Paul Sujkov wrote:

Hi everybody,

suppose I have two different parsers: one just reads the string, and 
another one parses some values from it. E.g.:


parseIntList :: Parser [Integer]
parseIntList = do
  char '('
  res <- liftM (map read) (sepBy1 (many1 digit) (char ';'))
  char ')'
  return res

parseIntString :: Parser String
parseIntString = manyTill anyChar eof

so for some input like this - "(1;2;3;4)" - I will have two different 
result:


*Parlog> parseTest parseIntList "(1;2;3;4)"
[1,2,3,4]
*Parlog> parseTest parseIntString "(1;2;3;4)"
"(1;2;3;4)"

but the thing that I actually want is something like Parser ([Integer], 
String) - results from both parsers at a time, no matter whether one of 
them fails or not:


*Parlog> parseTest parseIntListAndString "(1;2;3;4)"
([1,2,3,4], "(1;2;3;4)")

it is impossible at first sight, because first parser to use will 
consume all the input, and there will be nothing to parse for the second one


Parsec contains "choice" function, but it is implemented via <|> and 
that is mplus - so it tries second alternative only if the first one 
fails. Is it possible to use two parsers for the same string (with 
try-like backtracking, no input actually consumed till the second parser 
finishes)? I can assume only dirty hacks with the GenParser internals - 
manual position storing and backtracking - but that is obviously not good


however, my first attempt to solve the problem was kind a like that: to 
parse string to String, and then to use it as an input for the next 
level parse call:


parseIntListAndString :: Parser ([Integer], String)
parseIntListAndString = do
  str <- parseIntString
  return (res str, str)
  where res str = case (parse parseIntList "" str) of
Left  err -> []
Right val -> val

but the problems with such a method began when I switched from Parser to 
GenParser with user state: function parseIntList have to update the 
state, but it can't have the same state as the parseIntListAndString any 
more: it has it's own. I can explicitly pass the state from 
parseIntListAndString to parseIntList, but I see no suitable way for the 
parseIntList to update it. I can return the updated state value from the 
parseIntList function, and call setState on a result - but it seems 
rather ugly to mee. However, if nothing else will do, that is an alternative


it is of course possible to use two different parsers sequentially, but 
it is also very ineffective: I need to use such multiple parsing on a 
relatively small substring of the actual input, so little backtracking 
would be a much nicier approach. Any suggestions?


--
Regards, Paul Sujkov



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


Re: [Haskell-cafe] SQL Database in Haskell?

2009-08-05 Thread Don Stewart
gue.schmidt:
> Hi all,
>
> is there an SQL Database in Haskell or is there a project trying to  
> implement one?
>

There are several bindings,

http://hackage.haskell.org/packages/archive/pkg-list.html#cat:database

Are you asking for an implementation of SQL though?

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


Re: [Haskell-cafe] About the import module

2009-08-05 Thread andy morris
2009/8/5 xu zhang :
> Hi there,
>
> If I import a module and do not explicitly point out the entities I have
> imported. And I want the ghc to point out the entities automatically. Is
> there any method to do this? any methods to have the ghc point out the
> entities I import and export?
> Because there are so many files and I don't want to change them one by one,
> so I just want to find if there is a simple and automatic way to have the
> entities pointed out.
>
> Thank you in advance!
>

`ghc --make -ddump-minimal-imports Main.hs` will output *.imports
files containing what you want.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell2Xml

2009-08-05 Thread Dmitry Olshansky
Hello all,
I need a convenient tool to generate Haskell types from XML W3C Schema
Definition (xsd) and vice versa - generate instances for Haskell ADT's to
make corresponding XML.
It is just the same that HaXml do with DTD.

I need
- using XSD
- support for unicode
- using xml-attributes as far as elements are very desirable
- by my opinion TemplateHaskell for generate instances is prefferable than
using DrIFT (which used in HaXml) - both possibilities is great of course
- generation of xsd by Haskell type is a good feature also
and so on...

Does this tool exist?

Do some articles / thoughts / standards / recomendations about
correspondence between XML and Haskell ADT's exist?

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


Re: [Haskell-cafe] Efficient functional idiom for histogram

2009-08-05 Thread Dmitry Olshansky
> I got the impression Dmitry was using Haskell's standard RNG, not
> Mersenne Twister. If so, then we'd get further improvements with MT,
> but that's still a hit against Haskell, as I'd interpret it as meaning
> that Haskell supplies as default a PRNG which costs noticeable
> performance in order to provide guarantees that "ordinary" programs
> don't need.
>
> Paul.
>
Yes, I used standard RNG just made corrections from the second Daniel
Fischer's post. My file is attached. Commented strings are from original
version and next lines are from Daniel. (Note that "simulation" and
"simulate" types depend on type of "dice").
Just compile with ghc --make -O2 histogram.hs
and run
histogram +RTS -s

As a pre-intermediate ;-) I just check some proposals...


histogram.hs
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Basic questions about concurrency in Haskell

2009-08-05 Thread Sebastian Sylvan
On Wed, Aug 5, 2009 at 6:59 PM, Thomas Witzel wrote:
>
>
> 2. I started with the very simple nfib example given in the manual for
> Control.Parallel (Section 7.18). On my systems using multiple cores
> makes the code actually slower than just using a single core. While
> the manual cautions that this could be the case for certain
> algorithms, I'm wondering whether this is the desired behaviour for
> this example.
>
> I'm using ghc 6.10.4 right now.
>

IIRC the development version of GHC has some major work to optimize
concurrency, so it may be worth trying that. In particular I believe it
executes sparks in batches, to reduce the overhead (which hopefully fixes
your issue).


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


[Haskell-cafe] Space for commentaries on hackage

2009-08-05 Thread Maurí­cio CA

It would be nice to have a place for anonimous
comments below each page of a hackage package, maybe
with a cabal option to enable/disable that for a
particular package. Authors of packages with few
users may want that as a way to get first impressions
on their work they would otherwise not get. (At least,
I am, so I thought maybe others probably would.)


Best,
Maurício

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


Re: [Haskell-cafe] Basic questions about concurrency in Haskell

2009-08-05 Thread Bulat Ziganshin
Hello Thomas,

Wednesday, August 5, 2009, 9:59:00 PM, you wrote:

> because it provides facilities for concurrency on the language level,
> and I'm mainly interested in implementing parallel or massively
> parallel algorithms with Haskell. I have two questions that bother me.

if you plan to implement high-performance low-level algos, haskell/ghc
is definitely not the language you need. haskell concurrency features
are great in erlang-style situations when you need to manage many
threads that interacts in complex way. but don't expect to get any
C-level performance

> 1. Does the Haskell compiler make sure that there is no page sharing
> between threads

no

> 2. I started with the very simple nfib example given in the manual for
> Control.Parallel (Section 7.18).

standard optimization for this example is to use par only for large
enough n, otherwise you will lose much more time on synchronization.
ghc doesn't parallelize code in some wizardry way, it just have 4
worker threads, for example, and each spark created with par, becomes
one more job for these threads o execute


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Improving MPTC usability when fundeps aren't appropriate?

2009-08-05 Thread Daniel Peebles
Adding a dummy argument is what I've been doing so far, but it feels
hackish. Typeclasses add an implicit parameter containing the
dictionary of methods, and it seemed reasonable for me to have a more
direct influence over its value. If I must add another explicit
parameter to specify which dictionary to use, I might as well just
pass the dictionary around myself.

On Wed, Aug 5, 2009 at 12:56 PM, Bulat
Ziganshin wrote:
> Hello Daniel,
>
> Wednesday, August 5, 2009, 8:00:06 PM, you wrote:
>
>> class Moo a b where
>>   moo :: a -> a
>
>> instances. Another solution would be to artificially force moo to take
>> a "dummy" b so that the compiler can figure out which instance you
>> meant. That's what I've been doing in the mean time, but wouldn't it
>> be simpler and less hackish to add a some form of "instance
>> annotation", like a type annotation, that would make it possible to
>> specify what instance you wanted when it's ambiguous?
>
> imho, no. you propose to add one more feature when existing features
> can serve:
>
> class Moo a b where
>  moo :: a -> b -> a
>
> f x = moo x (undefined::Int)
>
> btw, may be associated types or associated type synonyms (these are
> novel features superseding FDs) is what you need?
>
>
>
> --
> Best regards,
>  Bulat                            mailto:bulat.zigans...@gmail.com
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] SQL Database in Haskell?

2009-08-05 Thread Günther Schmidt

Hi all,

is there an SQL Database in Haskell or is there a project trying to  
implement one?


Günther

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


[Haskell-cafe] About the import module

2009-08-05 Thread xu zhang
Hi there,

If I import a module and do not explicitly point out the entities I have
imported. And I want the ghc to point out the entities automatically. Is
there any method to do this? any methods to have the ghc point out the
entities I import and export?
Because there are so many files and I don't want to change them one by one,
so I just want to find if there is a simple and automatic way to have the
entities pointed out.

Thank you in advance!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Basic questions about concurrency in Haskell

2009-08-05 Thread Thomas Witzel
Hello all,

I'm new to Haskell, but have a good background in LISP/Scheme and do
mostly C/C++ programming on a daily basis. I'm learning Haskell mainly
because it provides facilities for concurrency on the language level,
and I'm mainly interested in implementing parallel or massively
parallel algorithms with Haskell. I have two questions that bother me.

1. Does the Haskell compiler make sure that there is no page sharing
between threads, in order to avoid cache thrashing between cpus (a
real killer on large SMP or ccNUMA systems) ? If so, are there
functions/options to control this ?

2. I started with the very simple nfib example given in the manual for
Control.Parallel (Section 7.18). On my systems using multiple cores
makes the code actually slower than just using a single core. While
the manual cautions that this could be the case for certain
algorithms, I'm wondering whether this is the desired behaviour for
this example.

I'm using ghc 6.10.4 right now.

Thank you for your help getting me started here.

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


[Haskell-cafe] Re: [Haskell Cafe] Parsec: using two different parser for the same string

2009-08-05 Thread Paul Sujkov
Well, I was too optimistic saying "I can return the updated state". I don't
know how to do that actually. Maybe someone else here knows?

2009/8/5 Paul Sujkov 

> Hi everybody,
>
> suppose I have two different parsers: one just reads the string, and
> another one parses some values from it. E.g.:
>
> parseIntList :: Parser [Integer]
> parseIntList = do
>   char '('
>   res <- liftM (map read) (sepBy1 (many1 digit) (char ';'))
>   char ')'
>   return res
>
> parseIntString :: Parser String
> parseIntString = manyTill anyChar eof
>
> so for some input like this - "(1;2;3;4)" - I will have two different
> result:
>
> *Parlog> parseTest parseIntList "(1;2;3;4)"
> [1,2,3,4]
> *Parlog> parseTest parseIntString "(1;2;3;4)"
> "(1;2;3;4)"
>
> but the thing that I actually want is something like Parser ([Integer],
> String) - results from both parsers at a time, no matter whether one of them
> fails or not:
>
> *Parlog> parseTest parseIntListAndString "(1;2;3;4)"
> ([1,2,3,4], "(1;2;3;4)")
>
> it is impossible at first sight, because first parser to use will consume
> all the input, and there will be nothing to parse for the second one
>
> Parsec contains "choice" function, but it is implemented via <|> and that
> is mplus - so it tries second alternative only if the first one fails. Is it
> possible to use two parsers for the same string (with try-like backtracking,
> no input actually consumed till the second parser finishes)? I can assume
> only dirty hacks with the GenParser internals - manual position storing and
> backtracking - but that is obviously not good
>
> however, my first attempt to solve the problem was kind a like that: to
> parse string to String, and then to use it as an input for the next level
> parse call:
>
> parseIntListAndString :: Parser ([Integer], String)
> parseIntListAndString = do
>   str <- parseIntString
>   return (res str, str)
>   where res str = case (parse parseIntList "" str) of
> Left  err -> []
> Right val -> val
>
> but the problems with such a method began when I switched from Parser to
> GenParser with user state: function parseIntList have to update the state,
> but it can't have the same state as the parseIntListAndString any more: it
> has it's own. I can explicitly pass the state from parseIntListAndString to
> parseIntList, but I see no suitable way for the parseIntList to update it. I
> can return the updated state value from the parseIntList function, and call
> setState on a result - but it seems rather ugly to mee. However, if nothing
> else will do, that is an alternative
>
> it is of course possible to use two different parsers sequentially, but it
> is also very ineffective: I need to use such multiple parsing on a
> relatively small substring of the actual input, so little backtracking would
> be a much nicier approach. Any suggestions?
>
> --
> Regards, Paul Sujkov
>



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


[Haskell-cafe] [Haskell Cafe] Parsec: using two different parser for the same string

2009-08-05 Thread Paul Sujkov
Hi everybody,

suppose I have two different parsers: one just reads the string, and another
one parses some values from it. E.g.:

parseIntList :: Parser [Integer]
parseIntList = do
  char '('
  res <- liftM (map read) (sepBy1 (many1 digit) (char ';'))
  char ')'
  return res

parseIntString :: Parser String
parseIntString = manyTill anyChar eof

so for some input like this - "(1;2;3;4)" - I will have two different
result:

*Parlog> parseTest parseIntList "(1;2;3;4)"
[1,2,3,4]
*Parlog> parseTest parseIntString "(1;2;3;4)"
"(1;2;3;4)"

but the thing that I actually want is something like Parser ([Integer],
String) - results from both parsers at a time, no matter whether one of them
fails or not:

*Parlog> parseTest parseIntListAndString "(1;2;3;4)"
([1,2,3,4], "(1;2;3;4)")

it is impossible at first sight, because first parser to use will consume
all the input, and there will be nothing to parse for the second one

Parsec contains "choice" function, but it is implemented via <|> and that is
mplus - so it tries second alternative only if the first one fails. Is it
possible to use two parsers for the same string (with try-like backtracking,
no input actually consumed till the second parser finishes)? I can assume
only dirty hacks with the GenParser internals - manual position storing and
backtracking - but that is obviously not good

however, my first attempt to solve the problem was kind a like that: to
parse string to String, and then to use it as an input for the next level
parse call:

parseIntListAndString :: Parser ([Integer], String)
parseIntListAndString = do
  str <- parseIntString
  return (res str, str)
  where res str = case (parse parseIntList "" str) of
Left  err -> []
Right val -> val

but the problems with such a method began when I switched from Parser to
GenParser with user state: function parseIntList have to update the state,
but it can't have the same state as the parseIntListAndString any more: it
has it's own. I can explicitly pass the state from parseIntListAndString to
parseIntList, but I see no suitable way for the parseIntList to update it. I
can return the updated state value from the parseIntList function, and call
setState on a result - but it seems rather ugly to mee. However, if nothing
else will do, that is an alternative

it is of course possible to use two different parsers sequentially, but it
is also very ineffective: I need to use such multiple parsing on a
relatively small substring of the actual input, so little backtracking would
be a much nicier approach. Any suggestions?

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


Re: [Haskell-cafe] Re: Thinking about what's missing in our library coverage

2009-08-05 Thread Don Stewart
gale:
> Other "batteries included" platforms contain
> various tools for processing markup that are
> far less general than pandoc. This is a place
> where Haskell can shine.
> 
> So yes, pandoc should definitely be included
> in the platform. All that said, though, I will
> certainly agree that it is not currently in the top 5.
> 

I agree with this. We would shine, but maybe not for the first cut.
Especially since the maintainer has requested this.

Note also: pandoc is GPL

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


Re: [Haskell-cafe] Re: Thinking about what's missing in our library coverage

2009-08-05 Thread Don Stewart
bulat.ziganshin:
> Hello Magnus,
> 
> Wednesday, August 5, 2009, 11:37:23 AM, you wrote:
> 
> > I don't know of any other way either.  I just strongly oppose the idea
> > that HP should take on the role of providing C lib bindings just
> > because on some platforms it's hard to satisfy the C dependencies.
> 
> those some platfroms are 97% of all dowanloads and success on these
> platforms is the key to overall Haskell success. moreover, asd i
> understand the situation, lack of package manager on Windows was main
> motivation to establish HP - for unicies it's not really required

The motivation was to have a high quality Haskell environment on every
system. That the unicies would all agree on what they provide was
"Haskell". Fixing up Windows was a nice side effect.

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


[Haskell-cafe] Re: Improving MPTC usability when fundeps aren't appropriate?

2009-08-05 Thread Heinrich Apfelmus
Daniel Peebles wrote:
> 
> I've been playing with multiparameter typeclasses recently and have
> written a few "uncallable methods" in the process. For example, in
> 
> class Moo a b where
>   moo :: a -> a
> 
> the moo function is effectively impossible to call (no amount of type
> annotations can tell the compiler what you intended b to be there).
> Some might suggest adding an a -> b functional dependency, but in some
> cases that is not appropriate, as there are multiple possible
> instances.

You can factor out  moo  into a type class involving only  a . And if
you can't do that, then you've got a problem with ambiguous instances
anyway.

> Another solution would be to artificially force moo to take
> a "dummy" b so that the compiler can figure out which instance you
> meant. That's what I've been doing in the mean time, but wouldn't it
> be simpler and less hackish to add a some form of "instance
> annotation", like a type annotation, that would make it possible to
> specify what instance you wanted when it's ambiguous? I'm not sure
> what syntax might be appropriate here, but it could also be seen as
> "opening" a particular instance, so something "open"-like might be
> good.

I don't think that the syntax for such a feature will be very different
from a dummy argument.

Also note that instead of using the actual type  b  as argument, as in

moo :: b -> a -> a

moo (undefined :: Foo) ...   -- usage

, you can use a phantom type

data Instance a = I

moo :: Instance b -> a -> a

bar = I :: Instance Bar
moo bar ...  -- usage



Regards,
apfelmus

--
http://apfelmus.nfshost.com

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


Re: [Haskell-cafe] Improving MPTC usability when fundeps aren't appropriate?

2009-08-05 Thread Bulat Ziganshin
Hello Daniel,

Wednesday, August 5, 2009, 8:00:06 PM, you wrote:

> class Moo a b where
>   moo :: a -> a

> instances. Another solution would be to artificially force moo to take
> a "dummy" b so that the compiler can figure out which instance you
> meant. That's what I've been doing in the mean time, but wouldn't it
> be simpler and less hackish to add a some form of "instance
> annotation", like a type annotation, that would make it possible to
> specify what instance you wanted when it's ambiguous?

imho, no. you propose to add one more feature when existing features
can serve:

class Moo a b where
  moo :: a -> b -> a

f x = moo x (undefined::Int)

btw, may be associated types or associated type synonyms (these are
novel features superseding FDs) is what you need?



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Re: Thinking about what's missing in our library coverage

2009-08-05 Thread Robin Green
And even if you don't agree with that, it would likely lead to
accidental use of GPL software in proprietary software, which is not a
good thing.
-- 
Robin

On Wed, 5 Aug 2009 09:33:34 -0700
"John A. De Goes"  wrote:

> 
> Tom is exactly right here. GPL is the kiss of death in the
> commercial world. Haskell Platform exists in part to encourage
> industry use of Haskell -- and to encourage "braindead" use of
> blessed libraries. GPL libraries have no place in HP.
> 
> Regards,
> 
> John A. De Goes
> N-Brain, Inc.
> The Evolution of Collaboration
> 
> http://www.n-brain.net|877-376-2724 x 101
> 
> On Aug 5, 2009, at 9:03 AM, Tom Tobin wrote:
> 
> > On Wed, Aug 5, 2009 at 10:46 AM, Colin Paul
> > Adams wrote:
> >>> "Tom" == Tom Tobin  writes:
> >>
> >>>> This can surely be tackled by cabal, as it already has the
> >>>> license information.
> >>
> >>Tom> I don't see this as a real solution; why would a package be
> >>
> >> It should be done anyway, irrespective of the platform.
> >
> > Yes, that would be handy option for cabal-install in general.
> >
> >
> >>Tom> added to the platform in the first place if a large
> >>Tom> proportion of developers couldn't make use of it?
> >>
> >> Anyone can make use of it. You may choose not to (or your boss may
> >> choose for you), but that doesn't mean you can't.
> >
> > The benefit of a standard library is that you can say "I need a
> > library to handle X" and if a library addressing X is in the
> > standard library, you're set.  If you then need to worry about the
> > GPL — and this is a reality that can't be written off as a mere
> > "choice" — why bother with the platform in the first place?
> > Non-GPL developers would be better off sticking with hackage in
> > that case. ___
> > 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


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


Re: [Haskell-cafe] Re: Thinking about what's missing in our library coverage

2009-08-05 Thread Robin Green
On Wed, 5 Aug 2009 11:03:55 -0500
Tom Tobin  wrote:

> On Wed, Aug 5, 2009 at 10:46 AM, Colin Paul
> Adams wrote:
> >> "Tom" == Tom Tobin  writes:
> >
> >    >> This can surely be tackled by cabal, as it already has the
> >    >> license information.
> >
> >    Tom> I don't see this as a real solution; why would a package be
> >
> > It should be done anyway, irrespective of the platform.
> 
> Yes, that would be handy option for cabal-install in general.

My feature request for this is here:

http://hackage.haskell.org/trac/hackage/ticket/481

where you can read a reply by Duncan listing some problems with this
idea.
-- 
Robin
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Thinking about what's missing in our library coverage

2009-08-05 Thread John A. De Goes


Tom is exactly right here. GPL is the kiss of death in the commercial  
world. Haskell Platform exists in part to encourage industry use of  
Haskell -- and to encourage "braindead" use of blessed libraries. GPL  
libraries have no place in HP.


Regards,

John A. De Goes
N-Brain, Inc.
The Evolution of Collaboration

http://www.n-brain.net|877-376-2724 x 101

On Aug 5, 2009, at 9:03 AM, Tom Tobin wrote:


On Wed, Aug 5, 2009 at 10:46 AM, Colin Paul
Adams wrote:

"Tom" == Tom Tobin  writes:


   >> This can surely be tackled by cabal, as it already has the
   >> license information.

   Tom> I don't see this as a real solution; why would a package be

It should be done anyway, irrespective of the platform.


Yes, that would be handy option for cabal-install in general.



   Tom> added to the platform in the first place if a large
   Tom> proportion of developers couldn't make use of it?

Anyone can make use of it. You may choose not to (or your boss may
choose for you), but that doesn't mean you can't.


The benefit of a standard library is that you can say "I need a
library to handle X" and if a library addressing X is in the standard
library, you're set.  If you then need to worry about the GPL — and
this is a reality that can't be written off as a mere "choice" — why
bother with the platform in the first place?  Non-GPL developers would
be better off sticking with hackage in that case.
___
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] Re: ANN: Typeful/Text/HTMLs (for AngloHaskell/for scrap?)

2009-08-05 Thread Jon Fairbairn
I wrote:
> You can get the whole thing with 
>
> darcs get --partial 
> http://homepage.ntlworld.com/jon.fairbairn/Typeful/Text/nHTMLs

but that was a temporary url that I copied and pasted. The correct one:

darcs get --partial 
http://homepage.ntlworld.com/jon.fairbairn/Typeful/Text/HTMLs

And I uploaded only a partial get because I don't have much space on
that server, but apparently darcs 2.3 can't get --partial from that
repo, so I've uploaded the whole thing for now.

Thanks to Max Desyatov for pointing out these problems.

And one of the tests failed because Bolivia is now the Plurinational
State of Bolivia, so I've add a patch for that. I've seen politics get
in the way of programming, but I've never had a bug caused by
/international/ politics before.

-- 
Jón Fairbairn jon.fairba...@cl.cam.ac.uk


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


Re: [Haskell-cafe] Typeclass for functions taking different kinds of strings

2009-08-05 Thread Neil Mitchell
Hi

> It looks nice but is not really a solution for passing large amounts
> of data efficiently. Converting everything to String creates too much
> overhead for large chunks of data.

There is uncons, which never creates big strings. But yes, adding more
bulk operations (i.e. lookup) might be necessary to make it widely
useful.

Thanks

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


Re: [Haskell-cafe] Re: Thinking about what's missing in our library coverage

2009-08-05 Thread Tom Tobin
On Wed, Aug 5, 2009 at 10:46 AM, Colin Paul
Adams wrote:
>> "Tom" == Tom Tobin  writes:
>
>    >> This can surely be tackled by cabal, as it already has the
>    >> license information.
>
>    Tom> I don't see this as a real solution; why would a package be
>
> It should be done anyway, irrespective of the platform.

Yes, that would be handy option for cabal-install in general.


>    Tom> added to the platform in the first place if a large
>    Tom> proportion of developers couldn't make use of it?
>
> Anyone can make use of it. You may choose not to (or your boss may
> choose for you), but that doesn't mean you can't.

The benefit of a standard library is that you can say "I need a
library to handle X" and if a library addressing X is in the standard
library, you're set.  If you then need to worry about the GPL — and
this is a reality that can't be written off as a mere "choice" — why
bother with the platform in the first place?  Non-GPL developers would
be better off sticking with hackage in that case.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: FFI: Problem with Signal Handler Interruptions

2009-08-05 Thread Levi Greenspan
Nobody?

On Tue, Aug 4, 2009 at 10:06 AM, Levi
Greenspan wrote:
> Dear list members,
>
> In February this year there was a posting "Why does sleep not work?"
> (http://www.haskell.org/pipermail/haskell-cafe/2009-February/055400.html).
> The problem was apparently caused by signal handler interruptions. I
> noticed the same (not with sleep though) when doing some FFI work and
> compiled the following test program:
>
>
> {-# LANGUAGE ForeignFunctionInterface #-}
> module Main where
>
> import Foreign.C.Types
> import Control.Concurrent
>
> sleep :: IO ()
> sleep = c_sleep 3 >>= print
>
> fails :: IO ()
> fails = sleep
>
> works :: IO ()
> works = forkIO sleep >> return ()
>
> main :: IO ()
> main = fails >> works >> threadDelay 300
>
> foreign import ccall unsafe "unistd.h sleep"
>    c_sleep :: CUInt -> IO CUInt
>
>
> When compiled with GHC (using --make -threaded), it will print 3
> immediately (from the "fails" function) and after 3 seconds 0 (from
> "works"), before it finally exits. man sleep(3) tells me that sleep
> returns 0 on success and if interrupted by a signal the number of
> seconds left to sleep. Clearly "fails" is interrupted by a signal
> (which seems to be SIGVTALRM). This was mentioned in the discussion
> from February.
>
> I would like to know why "fails" fails and "works" works, i.e. why is
> "sleep" not interrupted when run in a separate thread? And what can be
> done to make "sleep" work in the main thread? It wouldn't be wise to
> block SIGVTALRM, wouldn't it?
>
> Many thanks,
> Levi
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Improving MPTC usability when fundeps aren't appropriate?

2009-08-05 Thread Daniel Peebles
Hi all,

I've been playing with multiparameter typeclasses recently and have
written a few "uncallable methods" in the process. For example, in

class Moo a b where
  moo :: a -> a

the moo function is effectively impossible to call (no amount of type
annotations can tell the compiler what you intended b to be there).
Some might suggest adding an a -> b functional dependency, but in some
cases that is not appropriate, as there are multiple possible
instances. Another solution would be to artificially force moo to take
a "dummy" b so that the compiler can figure out which instance you
meant. That's what I've been doing in the mean time, but wouldn't it
be simpler and less hackish to add a some form of "instance
annotation", like a type annotation, that would make it possible to
specify what instance you wanted when it's ambiguous? I'm not sure
what syntax might be appropriate here, but it could also be seen as
"opening" a particular instance, so something "open"-like might be
good.

I don't know whether this has already been discussed much, but I was
unable to find anything that seemed relevant (beyond discussing
relationships between parametrized modules and typeclasses) but I
wanted to know if anyone had any opinion on adding such a feature to
(a future revision of) Haskell? I know people are generally reluctant
to add new syntax elements to a language, but considering the lack of
such a feature and the impossibility of writing such a thing in the
language itself, it seems like it'd be useful to add to the language
itself.

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


Re: [Haskell-cafe] Re: Thinking about what's missing in our library coverage

2009-08-05 Thread Colin Paul Adams
> "Tom" == Tom Tobin  writes:

>> This can surely be tackled by cabal, as it already has the
>> license information.

Tom> I don't see this as a real solution; why would a package be

It should be done anyway, irrespective of the platform.

Tom> added to the platform in the first place if a large
Tom> proportion of developers couldn't make use of it?

Anyone can make use of it. You may choose not to (or your boss may
choose for you), but that doesn't mean you can't.
-- 
Colin Adams
Preston Lancashire
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Efficient functional idiom for histogram

2009-08-05 Thread Paul Moore
2009/8/5 Yitzchak Gale :
> Dmitry Olshansky wrote:
>> My measurements show that...
>> (-O2 gives approx 2 time impovements).
>> ...using RandomGen and State monad to generate a list gives at least 4 times
>> improvements (on 1 000 000 items).
>
> You earlier said:
>
>> this takes over twice as long as a naively implemented
> Python program

The latter was me :-)

> So now our "naive" Haskell - ordinary usage of Data.Map
> and System.Random, without resorting to things like
> unboxed arrays - is beating naive Python handily. Correct?

I haven't checked myself (and won't have time in the next couple of
weeks, as I'm on holiday - but I'll pick this up when I get back).,
but it sounds like it. I'd like to check Dmitry's suggestions, mainly
to see how they fit with my feel for "naive" (ie, at my beginner
level, do I understand why they are more efficient).

But I'd expect (compiled) Haskell to beat (interpreted) Python. That's
sort of the point, really... The big measures for me are (1) by how
much, and (2) how readable is the code.

> Or is this with an alternate RNG? Although I think even that
> would be fair, since Python uses Mersenne.

I got the impression Dmitry was using Haskell's standard RNG, not
Mersenne Twister. If so, then we'd get further improvements with MT,
but that's still a hit against Haskell, as I'd interpret it as meaning
that Haskell supplies as default a PRNG which costs noticeable
performance in order to provide guarantees that "ordinary" programs
don't need.

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


Re: [Haskell-cafe] Re: Thinking about what's missing in our library coverage

2009-08-05 Thread Tom Tobin
On Wed, Aug 5, 2009 at 10:19 AM, Colin Paul
Adams wrote:
> Just because a library is blessed, doesn't mean you have to use it.

Then I'm not sure I understand the point of blessing it in a set of
libraries that "saves you the task of picking and choosing the best
Haskell libraries and tools to use for a task" if "task" (in the
second mention) is limited to "developing GPL'd software".  The
"picking and choosing" problem immediately comes back for everyone
else, leaving the platform with second-class users who are forced to
evaluate the libraries to make sure they're legally compatible —
defeating the purpose of the platform.

> This can surely be tackled by cabal, as it already has the license 
> information.

I don't see this as a real solution; why would a package be added to
the platform in the first place if a large proportion of developers
couldn't make use of it?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Thinking about what's missing in our library coverage

2009-08-05 Thread Colin Paul Adams
> "Tom" == Tom Tobin  writes:


Tom> As I understand it, Pandoc is entirely under the GPL (not
Tom> LGPL).  I'd be very wary of accepting a GPL'd library as a

I'd be very upset if pandoc weren't blessed.

Tom> blessed "standard" library, since it would be completely
Tom> unusable for non-GPL projects.

This can surely be tackled by cabal, as it already has the license
information.

So if you were to specify you project has a BSD license, and it
requires use of a library licensed under the GPL, then cabal configure
should fail with an error message.

Just because a library is blessed, doesn't mean you have to use it.
-- 
Colin Adams
Preston Lancashire
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Thinking about what's missing in our library coverage

2009-08-05 Thread Yitzchak Gale
Tom Tobin wrote:
> As I understand it, Pandoc is entirely under the GPL (not LGPL).

Oh. That would be an issue, yes. Too bad.

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


Re: [Haskell-cafe] Re: Thinking about what's missing in our library coverage

2009-08-05 Thread Tom Tobin
On Wed, Aug 5, 2009 at 8:28 AM, Yitzchak Gale wrote:
> I agree with most of Alexander's many thoughtful comments
> about Don's list of potential additions to HP. But I
> disagree about pandoc.
[...]
> So yes, pandoc should definitely be included
> in the platform.

I should preface this by saying that while I'm an experienced Python
programmer, I'm *very* new to Haskell.

As I understand it, Pandoc is entirely under the GPL (not LGPL).  I'd
be very wary of accepting a GPL'd library as a blessed "standard"
library, since it would be completely unusable for non-GPL projects.
One of the nice things about the Python standard library is that you
know it's liberally licensed; a programmer can feel free to use it for
any project, whether proprietary or copyleft or otherwise.  I don't
think I'd feel comfortable using or recommending the Haskell Platform
if "batteries included" came with such a serious caveat.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Efficient functional idiom for histogram

2009-08-05 Thread Yitzchak Gale
Dmitry Olshansky wrote:
> My measurements show that...
> (-O2 gives approx 2 time impovements).
> ...using RandomGen and State monad to generate a list gives at least 4 times
> improvements (on 1 000 000 items).

You earlier said:

> this takes over twice as long as a naively implemented
Python program

So now our "naive" Haskell - ordinary usage of Data.Map
and System.Random, without resorting to things like
unboxed arrays - is beating naive Python handily. Correct?

Or is this with an alternate RNG? Although I think even that
would be fair, since Python uses Mersenne.

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


Re: [Haskell-cafe] Typeclass for functions taking different kinds of strings

2009-08-05 Thread Taru Karttunen
Excerpts from Neil Mitchell's message of Wed Aug 05 16:36:06 +0300 2009:
> I currently use this library:
> 
> http://community.haskell.org/~ndm/darcs/tagsoup/Text/StringLike.hs
> 

It looks nice but is not really a solution for passing large amounts
of data efficiently. Converting everything to String creates too much
overhead for large chunks of data.

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


Re: [Haskell-cafe] Typeclass for functions taking different kinds of strings

2009-08-05 Thread Neil Mitchell
Hi

> is there currently a library that makes unifying them easy?

I currently use this library:

http://community.haskell.org/~ndm/darcs/tagsoup/Text/StringLike.hs

Not yet released, and rather specific to what I was wanting to do, but
does work for me. I'm happy for people to steal bits from that as they
want.

Thanks

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


Re: [Haskell-cafe] Re: Thinking about what's missing in our library coverage

2009-08-05 Thread Yitzchak Gale
I agree with most of Alexander's many thoughtful comments
about Don's list of potential additions to HP. But I
disagree about pandoc.

Alexander Dunlap wrote:
> No. Pandoc is too actively developed to go into the HP.

It depends on the nature of the development. If the
API is currently very unstable and is expected to
stabilize soon, then wait a little bit. Otherwise, that is
no excuse to exclude something worthwhile.
Choose a well-tested numbered version and include
it.

Later, if we want to upgrade, just follow the usual
deprecation-upgrade process.

Umm - we do have a well-defined deprecation-upgrade
process, don't we?

> It's also much more of an end-user application than
> a "standard library"

pandoc provides an extensive library, and also a
command-line app. Is it a policy that in such a case,
we require the command-line app to be split off into
a separate package before we can include it?

I'm not sure that's so important, but if so, it should
not be hard to do that for pandoc.

> its applications are not general
> enough to be included in the standard
> distribution.

Text with markup is used in some way for almost
every application. This library provides tools to
convert between a wide variety of markup
formats. Sounds pretty general to me.

Other "batteries included" platforms contain
various tools for processing markup that are
far less general than pandoc. This is a place
where Haskell can shine.

So yes, pandoc should definitely be included
in the platform. All that said, though, I will
certainly agree that it is not currently in the top 5.

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


Re: [Haskell-cafe] Efficient functional idiom for histogram

2009-08-05 Thread Dmitry Olshansky
My measurements show that
- using strict version of insertWith doesn't improve performance. - in case
of compilation with -O2 flag foldl' also is equal to foldl (-O2 gives approx
2 time impovements).- using RandomGen and State monad to generate a list
gives at least 4 times improvements (on 1 000 000 items).

More complicated improvements (using Array, PRNG and so on) were not tested
by me.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell interface files: Why used? What about same data in object files?

2009-08-05 Thread Malcolm Wallace

for some changes of .hs file (where just
the implementation changes) the .o file can be regenerated without
touching the .hi file. This allows more accurate build dependencies
and less recompilation.


Is that really the case?  I thought that GHC may add code to the
interface files for cross-module inlining purposes, which means that
changing the implementation might change the interface too.


Indeed, GHC _may_ change the interface file for such reasons, but it  
may equally decide to leave the interface untouched, e.g. if there are  
no new inlinings.


Regards,
Malcolm

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


Re: [Haskell-cafe] powerSet = filterM (const [True, False]) and Data.List permutation

2009-08-05 Thread Jan Christiansen

Hi,

i am replying to a thread called "Data.List permutations"  on ghc- 
users and a thread called "powerSet = filterM (const [True,  
False]) ... is  this obfuscated haskell?" on haskell cafe.


On 04.08.2009, at 19:48, Slavomir Kaslev wrote:

A friend mine, new to functional programming, was entertaining  
himself by
writing different combinatorial algorithms in Haskell. He asked me  
for some
help so I sent him my quick and dirty solutions for generating  
variations and

permutations:



On the haskell cafe thread it was observed that you can implement the  
permutations function in a non-deterministic favour. The ideas behind  
these implementations closely resemble implementations of  
corresponding functions in Curry.


We can generalise your implementation to an arbitrary MonadPlus. The  
idea is that the MonadPlus represents non-determinism. `inter` non- 
deterministically inserts an element to every possible position of its  
argument list.


inter x [] = [[x]]

inter x yys@(y:ys) = [x:yys] ++ map (y:) (inter x ys)


interM :: MonadPlus m => a -> [a] -> m [a]
interM x [] = return [x]
interM x yys@(y:ys) =
 return (x:yys)
   `mplus`
 liftM (y:) (interM x ys)


perm [] = [[]]
perm (x:xs) = concatMap (inter x) (perm xs)


permM :: MonadPlus m => [a] -> m [a]
permM [] = return []
permM (x:xs) = interM x =<< permM xs

Alternatively we can implement permM by means of foldM.

permM :: MonadPlus m => [a] -> m [a]
permM = foldM (flip interM) []

A standard example for the use of non-determinism in Curry is a perm  
function that looks very similar to `permM` with the slight difference  
that you do not need the monad in Curry.



An alternative to this definition is to define a monadic version of  
insertion sort. First we define a monadic equivalent of the `insertBy`  
function as follows:


-- insertBy :: (a -> a -> Bool) -> a -> [a] -> [a]
-- insertBy _ x [] = [x]
-- insertBy le x (y:ys) =--  if le x y-- then x:y:ys
-- else y:insertBy le x ys

insertByM :: MonadPlus m => (a -> a -> m Bool) -> a -> [a] -> m [a]
insertByM _ x [] = return [x]
insertByM le x (y:ys) = do
 b <- le x y
 if b
then return (x:y:ys)
else liftM (y:) (insertByM le x ys)

Note that this function is very similar to interM, that is, we have

 interM = insertByM (\_ _ -> return False `mplus` return True)

On basis of `insertBy` we can define insertion sort.

-- sortBy :: (a -> a -> Bool) -> [a] -> [a]
-- sortBy le = foldr (insertBy le) []

In the same manner we can define a function `sortByM` by means of  
`insertByM`.


sortByM :: MonadPlus m => (a -> a -> m Bool) -> [a] -> m [a]
sortByM le = foldM (flip (insertByM le)) []

Now we can define a function that enumerates all permutations by means  
of `sortByM`.


permM :: MonadPlus m => [a] -> m [a]
permM = sortByM (\_ _ -> return False `mplus` return True)


Interestingly we can also define permM by means of monadic  
counterparts of other sorting algorithms like mergeSort. Although  
there were some arguments on haskell cafe that this would not work for  
other sorting algorithms it looks like this is not the case. At least  
the corresponding implementation of perm by means of mergeSort in  
Curry works well for lists that I can test in reasonable time.


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


Re: [Haskell-cafe] Typeclass for functions taking different kinds of strings

2009-08-05 Thread Johan Tibell
On Wed, Aug 5, 2009 at 1:24 PM, Taru Karttunen  wrote:

> Hello
>
> It seems like a very common issue to have an API like:
>
> foo   :: String -> Foo
> fooBS :: ByteString -> Foo
> fooLBS:: L.ByteString -> Foo
>
> is there currently a library that makes unifying them easy?
>

They cannot be completely unified. A sequence of Unicode characters (String)
is not the same kind of thing as a sequence of bytes (ByteString). Going
between the two requires an encoding. A shared abstraction would support a
subset of operations that make sense on all sequences.

Cheers,

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


[Haskell-cafe] Typeclass for functions taking different kinds of strings

2009-08-05 Thread Taru Karttunen
Hello

It seems like a very common issue to have an API like:

foo   :: String -> Foo
fooBS :: ByteString -> Foo
fooLBS:: L.ByteString -> Foo

is there currently a library that makes unifying them easy?

Below is attached one try at this, does it make sense? I'm thinking of
uploading it to Hackage but would like comments first.

With the library the above code is transformed into:

foo :: StringLike string => string -> Foo


- Taru Karttunen


StringLike.hs
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Getting highest sum of list elements with Map

2009-08-05 Thread Yitzchak Gale
Hi Gwern,

gwern0 wrote:
> ...efficiency is an issue.

Here are a few efficiency issues that I noticed in your algorithm
after a quick look (none of these have to do with Haskell really):

o ranks sorts the entire set, then discards all but the maximum.
  It would be better to use maximum or maximumBy.
  If you are worried about the empty set, check that separately.

o You recompute the same rank value repeatedly for every word
  in each sentence. Use a "let" clause in your list comprehension
  to do it only once per sentence.

o approximation rescans the entire corpus after discarding each
  word. Try to think of a way to recompute only those sentences
  that contained the word.

Hope this helps,
Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: Typeful/Text/HTMLs (for AngloHaskell/for scrap?)

2009-08-05 Thread Jon Fairbairn

A while ago I wrote this rather pedantic html library (it guarantees
standards compliance via types, even down to the nesting restrictions).
I announced it on the libraries list, but chronic fatigue gets in the
way of following things up, so I haven't taken it any further until
recently. And recently there have been other efforts in the HTML area
that may make it out of date.

Anyway, I think there are one or two useful ideas in it, and if I manage
to get to AngloHaskell, I'd like to discuss it a bit, hence the
announcement (rather closer to AH than I intended).

You can get the whole thing with 

darcs get --partial 
http://homepage.ntlworld.com/jon.fairbairn/Typeful/Text/nHTMLs
It should build with ghc 6.10 and haddock 2.4.2

or you can browse the documentation starting at 


and AngloHaskell people who are interested might want to look at



-- 
Jón Fairbairn jon.fairba...@cl.cam.ac.uk

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


[Haskell-cafe] Getting highest sum of list elements with Map

2009-08-05 Thread gwern0
-- based on http://jtauber.com/blog/2008/02/10/a_new_kind_of_graded_reader/
-- TODO: read knownwords from file
--   print out matching sentences as well (make optional)
--   fix performance; goal: handle Frank Herbert corpus in under 5 minutes
--   benchmark parallelism; is it gaining me anything or is 'pmap' just wasting 4 lines?

import Data.Char (isPunctuation, toLower)
import Data.List -- (nub, sort)
import qualified Data.Set as Set
import qualified Data.Map as Map
import Control.Parallel.Strategies
import Data.Function (on)
import Data.Maybe

import Data.List.Split (splitWhen)

import System.IO.UTF8 (getContents, putStrLn)
import System.Environment (getArgs)

main :: IO ()
main = do depth <- fmap (read . head) $ getArgs
  corpus <- System.IO.UTF8.getContents
  let pcorpus = processCorpus corpus
  let knownwords = map (map toLower) ["You", "dont", "see", "more", "than", "that", "The", "first", "episode", "of", "Kare", "Kano", "is", "rotten", "with", "Evangelion", "visual", "motifs", "the", "trains", "the", "spotlights", "and", "telephone", "poles", "and", "wires", "the", "masks", "and", "this", "is", "how", "everyone", "sees", "me", "etc", "a", "it", "did", "are", "to", "in", "I", "Dune", "was", "Stalin", "Mussolini", "Hitler", "Churchill", "beginning", "That", "all", "be", "like", "on", "an", "Its", "But", "only", "you", "themes", "into", "as", "my", "human", "paradox","he","said","paul","his","she","her","not","him","had","for","at","alia","no","from","what","asked","they","there","have","stilgar"]
  let optimalwords = answer depth pcorpus knownwords
  System.IO.UTF8.putStrLn optimalwords

-- | Clean up. Don't want 'Je suis." to look different from "Je suis"...
--
-- > stringPunctuation "Greetings, fellow human flesh-sacks!" ~> "Greetings fellow human fleshsacks"
stripPunctuation :: String -> String
stripPunctuation = filter (not . isPunctuation)

-- Turn a single big document into a stream of sentences of individual words; lower-case so we don't get
-- multiple hits for 'He', 'he' etc
processCorpus :: String -> [[String]]
processCorpus = pmap (sort . words . stripPunctuation) . splitWhen (=='.') . map toLower

-- parallel map
pmap :: (NFData b) =>(a -> b) -> [a] -> [b]
pmap = parMap rnf

sentences :: (NFData a, Ord a) => [[a]] -> Map.Map Int (Set.Set a)
sentences = Map.fromList . zip [(0::Int)..] . pmap Set.fromList

fidiv :: (Integral a, Fractional b) => a -> a -> b
fidiv = (/) `on` fromIntegral

swap :: (a, b) -> (b, a)
swap = uncurry (flip (,))

ranks :: (NFData v, Ord k, Ord v) => Map.Map k (Set.Set v) -> Maybe (Rational, v)
ranks s =  listToMaybe . sortBy (flip compare) .
  pmap swap .
  Map.toList .
  Map.fromListWith (+) $
  [(word, 1 `fidiv` Set.size wrds)
  | (_sentenceId, wrds) <- Map.toList s
  , word <- Set.toList wrds]

approximation :: (NFData v, Ord k, Ord v) => Map.Map k (Set.Set v) -> Int -> [v]
approximation _ 0 = []
approximation s n =
case ranks s of
  Nothing -> []
  Just (_value, word) ->
let withoutWord = Map.map (Set.delete word) s
in word : approximation withoutWord (n-1)

-- do not use parmap in this function on pain of death; GHC is broken?
process :: (Ord v, NFData v) => [[v]] -> [Int] -> [[v]]
process ss ns = map (approximation $ sentences ss) ns

getBest :: [Int] ->[[String]] -> String
getBest x y = unlines . last  $ process y x

filterKnown :: [String] -> [[String]] -> [[String]]
filterKnown known = filter (not . null) . pmap (filter (flip notElem $ known))

answer :: Int -> [[String]] -> [String] -> String
answer depth corp known = let corp' = filterKnown known corp in getBest  [1..depth] corp'___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] Re: Thinking about what's missing in our library coverage

2009-08-05 Thread Magnus Therning
On Wed, Aug 5, 2009 at 8:59 AM, Bulat
Ziganshin wrote:
> Hello Magnus,
>
> Wednesday, August 5, 2009, 11:37:23 AM, you wrote:
>
>> I don't know of any other way either.  I just strongly oppose the idea
>> that HP should take on the role of providing C lib bindings just
>> because on some platforms it's hard to satisfy the C dependencies.
>
> those some platfroms are 97% of all dowanloads and success on these
> platforms is the key to overall Haskell success. moreover, asd i
> understand the situation, lack of package manager on Windows was main
> motivation to establish HP - for unicies it's not really required

80% of all internet-related statistics are made dubious ;-)

I strongly doubt the "97% of all downloads" statement.  However,
that's not really what we are discussing here.  This is the statement
on the Haskell Platform page:

"The Haskell Platform is a blessed library and tool suite for Haskell
distilled from Hackage, along with installers for a wide variety of
machines. The contents of the platform is specified here: Haskell:
Batteries Included.

"The platform saves you the task of picking and choosing the best
Haskell libraries and tools to use for a task. Distro maintainers that
support the Haskell Platform can be confident they're fully supporting
Haskell as the developers intend it. Developers targetting the
platform can be confident they have a trusted base of code to work
with."

The way _I_ read it, HP is a set of libraries that form a supplement
to a Haskell compiler/interpreter.  Developers can feel confident
writing code against this set of libraries and it's the goal to make
HP available on as many platforms as possible.

I don't think that establishing HP was mainly motivated by the lack of
a package manager for windows, I also don't think that HP is un-needed
on Unices.  AFAIU the motivation was to 1) separate the
compiler/interpreter (especially GHC) from "base libraries", 2) to
clearly communicate what Haskell packages a developer can expect to
find on a "Haskell system", and 3) to provide users/developers with an
easy route to setting up a "Haskell system" on different OSs.

Difficulty to build a C dependency of a Haskell library should _not_
be a criterion used to decide whether the Haskell library goes into HP
or not.

Cabal is great for source distribution, but apparently there's a need
for a binary packager, especially for Windows.

/M

-- 
Magnus Therning(OpenPGP: 0xAB4DFBA4)
magnus@therning.org  Jabber: magnus@therning.org
http://therning.org/magnus identi.ca|twitter: magthe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell interface files: Why used? What about same data in object files?

2009-08-05 Thread Iavor Diatchki
Hello,

On Tue, Aug 4, 2009 at 2:50 PM, Neil Mitchell wrote:
> Hi
>
>> Some good reasons for having a separate interface are:  they can be
>> human-readable and human-writable (ghc's do not fulfill this criterion);
>> they can be used to bootstrap mutually recursive modules in the absence of
>> any object files (ghc uses .hs-boot files instead); other tools can extract
>> information about modules without having to understand either the full
>> Haskell syntax or the object language.
>
> An additional reason is that for some changes of .hs file (where just
> the implementation changes) the .o file can be regenerated without
> touching the .hi file. This allows more accurate build dependencies
> and less recompilation.

Is that really the case?  I thought that GHC may add code to the
interface files for cross-module inlining purposes, which means that
changing the implementation might change the interface too.
-Iavor
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Re: Thinking about what's missing in our library coverage

2009-08-05 Thread Bulat Ziganshin
Hello Magnus,

Wednesday, August 5, 2009, 11:37:23 AM, you wrote:

> I don't know of any other way either.  I just strongly oppose the idea
> that HP should take on the role of providing C lib bindings just
> because on some platforms it's hard to satisfy the C dependencies.

those some platfroms are 97% of all dowanloads and success on these
platforms is the key to overall Haskell success. moreover, asd i
understand the situation, lack of package manager on Windows was main
motivation to establish HP - for unicies it's not really required


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Re: Thinking about what's missing in our library coverage

2009-08-05 Thread Magnus Therning
On Tue, Aug 4, 2009 at 11:05 PM, Max Rabkin wrote:
> On Tue, Aug 4, 2009 at 11:56 PM, Magnus Therning wrote:
>>>
>>> AIUI, on systems with working package managers, HP will be a
>>> metapackage which depends on the appropriate "real" packages.
>>
>> Yes, but again, the role of HP shouldn't be to limit the pain of installing
>> bindings to C libraries.  What I'm saying is that it's a worthwhile goal to
>> limit that pain, but it should be handled outside of HP.
>
> How could one do that? On systems with package managers, the platform
> won't bundle C libraries, but depend on them (this is correct: if
> software does in fact depend on a C library, it should declare that
> dependency). On systems without package managers, we could provide
> some form of "sub-platform" containing C libraries or a system for
> installing them, but then installing a Haskell system is no longer a
> one-step process.

Well, I'd hope that the stuff that's being built around _building_ HP
(helper scripts / procedures for putting together binary installers on
Mac and Win) is general enough so that it can be used to do a HP+ (or
a number of installers) that includes different C lib bindings.  In
essence, that would result in a set of prepared Haskell packages for
the platforms that lack a good package manager.

> It's been a while since I was a regular Windows user, but it seemed
> then that bundling dependencies was the most common (only?) solution.

I don't know of any other way either.  I just strongly oppose the idea
that HP should take on the role of providing C lib bindings just
because on some platforms it's hard to satisfy the C dependencies.

/M

-- 
Magnus Therning(OpenPGP: 0xAB4DFBA4)
magnus@therning.org  Jabber: magnus@therning.org
http://therning.org/magnus identi.ca|twitter: magthe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe