Re: [Haskell-cafe] Re: Problems with strictness analysis?

2008-11-05 Thread wren ng thornton

Luke Palmer wrote:

The example being discussed in this thread is a good one:

  sum [1..10^8] + length [1..10^8]

With Haskell's semantics, we know we can write this as:

  let xs = [1..10^8] in sum xs + length xs

But it causes a change in memory *complexity*, so in some sense these
two sentences are not equal.  What is the theory in which we can
observe this fact?  Is it possible to give a simple denotational
semantics which captures it?


There's actually been a good deal of work on trying to mathematize this 
sort of issue, under the name of linear logic[1]. The problem with 
classical equational reasoning is that it doesn't capture the notion of 
"resources" or the "sharing" thereof. The two expressions are not the 
same because the first has two [1..10^8] resources it can use up, 
whereas the later only has one. Depending on the balance between sharing 
 temporal work vs minimizing memory overhead, sometimes it's okay to 
add sharing and other times it's okay to remove it, but in general both 
options are not available at once.


It's pretty easy to capture issues of economy with LL, though making a 
rewriting system takes a bit more framework. I'm not sure to what extent 
LL has been explored as a semantic model for programs, but Clean[2] and 
Phil Wadler[3] have certainly done very similar work.



[1] 
[2] 
[3] 

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


Re: Re: [Haskell-cafe] Problems with strictness analysis?

2008-11-05 Thread Kim-Ee Yeoh


Luke Palmer-2 wrote:
> 
> I would like to know or to develop a way to allow abstract 
> analysis of time and space complexity.
> 

In the same way that type inference and strictness analysis can be
seen as instances of abstract interpretation, so can complexity
inference. I agree that the interplay between these various instances
of AI is an unexplored lode for us cogheads.

Below are 2 references to complexity inference. I have yet to look
closely to ascertain the degree of compositionality of their
methodologies. Can anyone recommend a survey paper of the 
entire field?

Linear, Polynomial or Exponential? Complexity Inference in Polynomial Time
Amir M. Ben-Amram, Neil D. Jones and Lars Kristiansen  
http://dx.doi.org/10.1017/S095679683865

Automated complexity analysis of Nuprl extracted programs
Ralph Benzinger
http://dx.doi.org/10.1007/978-3-540-69407-6_7

-- 
View this message in context: 
http://www.nabble.com/Problems-with-strictness-analysis--tp20301967p2034.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


Re: [Haskell-cafe] pure programs

2008-11-05 Thread Conal Elliott
Hi Jason,

To help me understand your question, would you be unhappy with the following
structure?

-- runnable
main = interact f
-- composable
f = ...

The discipline is to use interact (or another combinator) to wrap a
functional/composable/pure component like f into an executable.  Then give
main to users and f to programmers.  This same game can be made more
sophisticated, eg

main = interact (show . f . read)

Or unparse & parse in place of show & read.

For more on combining usability and composability, see

http://haskell.org/haskellwiki/TV

http://conal.net/blog/posts/tangible-functional-programming-a-modern-marriage-of-usability-and-composability/

- Conal

On Tue, Nov 4, 2008 at 4:12 PM, Jason Dusek <[EMAIL PROTECTED]> wrote:

>  Informally, a "pure program" an executable such that the
>  stream of bytes entering it totally determines the stream of
>  bytes leaving it.
>
>  Many useful programs that I would like to write in Haskell
>  don't fall into this category -- for example, network servers
>  -- but a lot of their components do. Can these components can
>  be Haskell functions without IO in their signatures?
>
>  Though that seems reasonable, it is not, in general, true. For
>  example,System.Info.osis generally treated as pure,
>  though it is not. It's not clear to me how to disambiguate
>  these "born again" values from really pure values.
>
> --
> _jsn
> ___
> 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] Re: Problems with strictness analysis?

2008-11-05 Thread Claus Reinke

  equational /= denotational


Nonetheless, Haskell has equational semantics which are derived from
its denotational ones.  But when I said "equational semantics" I
really meant something more like "equations" :-).


Unlike Standard ML, for instance, Haskell does not have standard
semantics - a persistent embarrassment. There are semantics for fragments,
but no guarantee that any of them will match any part of the language, let 
alone its implementations.


One can base equational semantics on denotational semantics, but that is 
not the only way, hence the two are not equal. I was trying to point out
the missing part, where equations are are useful for operational reasoning, 
beyond simple denotations.



Sometimes, operational semantics based
on directed equations give you the best of both worlds: equational reasoning
and behavioural guidelines, both at a suitably "clean" and abstract level.


By directed equations you mean unidirectional rewrite rules?


Yes. Think of rewriting (replacing old with new) as a general form 
of operational semantics.Within this form, there is a wide range of 
possibilities, including rewriting abstract machine states and rewriting

source-level programs. Somewhere near the latter, there is a "most
abstract" form of operational semantics for a language, one for which
every other form adds details that are not inherent in the language, but
are artifacts of the formalisation (details of the abstract machine, or
details of the mathematical domain, or ..).


But I'd like to back up a bit.  I may have been too quick to assign
the judgement "dirty" to operational thinking.  I am not asking this
question as a complaint, as a challenge on the language, or as any
other such rhetorical device: my question is earnest.  I would like to
know or to develop a way to allow abstract analysis of time and space
complexity.


So you want to reason about the way from the original program to its
outputs, not just about the outputs. You can cling to denotations, by 
extending mere values with information about the computation leading

to those values, but why not reason about the computation directly.

In logic terms, you want to talk about the proof, not just about the
truth of your theorems. In functional language terms, you want to talk
about reductions, not just about normal forms. This works well for
pure lambda calculus, and has been extended to cover other aspects
of Haskell implementations, such as call-by-need lambda calculus as
a way for evaluation of non-strict programs with sharing.

   The call-by-need lambda calculus
   John Maraist and Martin Odersky and Philip Wadler
   Journal of Functional Programming, 1998
   http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.44.5259

The idea is to use "let" to represent sharing, and to refine the reduction
rules to take this into account: instead of substituting parameters into
function bodies, parameter bindings are kept in "let"-bindings, where
their evaluation is shared (only values can be substituted, so substitution
is preceded by evaluation, when needed).

The resulting reductions are quite a bit more involved than without
sharing, because all reductions take place within a context (those
"let"-bindings). But that is quite close to what happens in a compiled
graph reduction implementation: those "let"-bindings represent the
heap, the nested contexts correspond to stack.

(there are of course optimizations and representation changes that affect 
performance, but the former are themselves expressed as rewrite rules,
and the latter can be accounted for by refining the rewrite system, when 
such details are needed - luckily, that isn't often the case)



On my time working with Haskell, I've developed a pretty accurate
"intuition" about the performance of programs.  It is some meld of
thinking in terms of the lazy evaluation mechanism, some higher-level
rules of thumb about when new thunks are allocated, and probably some
other stuff hiding in the depths of my brain.  I know it, but I am not
satisfied with it, because I can't formalize it.  I wouldn't be able
to write them down and explain to a fellow mathematician how I reason
about Haskell programs.

The example being discussed in this thread is a good one:

 sum [1..10^8] + length [1..10^8]

With Haskell's semantics, we know we can write this as:

 let xs = [1..10^8] in sum xs + length xs

But it causes a change in memory *complexity*, so in some sense these
two sentences are not equal.  What is the theory in which we can
observe this fact?  Is it possible to give a simple denotational
semantics which captures it?


Why do you insist on denotational semantics for reasoning about evaluation?
Denotational semantics are best when all you care about are values.

Have a look at that paper, or the earlier version

   http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.39.2287

There is also

   John Launchbury, A Natural Semantics for Lazy Evaluation,1993
   http://citeseerx.ist.psu.e

Re[2]: [Haskell-cafe] Re: Problems with strictness analysis?

2008-11-05 Thread Bulat Ziganshin
Hello Luke,

Thursday, November 6, 2008, 2:34:36 AM, you wrote:

> The example being discussed in this thread is a good one:

>   sum [1..10^8] + length [1..10^8]

> With Haskell's semantics, we know we can write this as:

>   let xs = [1..10^8] in sum xs + length xs

> But it causes a change in memory *complexity*, so in some sense these
> two sentences are not equal.  What is the theory in which we can
> observe this fact?  Is it possible to give a simple denotational
> semantics which captures it?

i'm not a mathematician, but why you can't explore term rewriting
system? it has some graph at initial stage and modifies it until normal
form is reached. graphs representing first and second expression are
different (first is tree while second have two two links to [1..10^8]
node) and this oes to difference between their evaluation process. on
the every step of rewriting of first graph itssize remains O(1), while
second graph during rewriting grows up to O(n) size


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Re: Problems with strictness analysis?

2008-11-05 Thread Luke Palmer
On Wed, Nov 5, 2008 at 1:24 AM, Claus Reinke <[EMAIL PROTECTED]> wrote:
>> How can we support analysis of time and space complexity without
>> expanding ourselves into the complicated dirty world of operational
>> thinking?
>
>   equational /= denotational

Nonetheless, Haskell has equational semantics which are derived from
its denotational ones.  But when I said "equational semantics" I
really meant something more like "equations" :-).

>   operational /= bad
>
> Sometimes, denotational is too abstract, offering no guidelines on
> behaviour, just as abstract machine based operational thinking is too
> concrete, hiding
> the insights in a flood of details. Sometimes, operational semantics based
> on directed equations give you the best of both worlds: equational reasoning
> and behavioural guidelines, both at a suitably "clean" and abstract level.

By directed equations you mean unidirectional rewrite rules?

But I'd like to back up a bit.  I may have been too quick to assign
the judgement "dirty" to operational thinking.  I am not asking this
question as a complaint, as a challenge on the language, or as any
other such rhetorical device: my question is earnest.  I would like to
know or to develop a way to allow abstract analysis of time and space
complexity.

On my time working with Haskell, I've developed a pretty accurate
"intuition" about the performance of programs.  It is some meld of
thinking in terms of the lazy evaluation mechanism, some higher-level
rules of thumb about when new thunks are allocated, and probably some
other stuff hiding in the depths of my brain.  I know it, but I am not
satisfied with it, because I can't formalize it.  I wouldn't be able
to write them down and explain to a fellow mathematician how I reason
about Haskell programs.

The example being discussed in this thread is a good one:

  sum [1..10^8] + length [1..10^8]

With Haskell's semantics, we know we can write this as:

  let xs = [1..10^8] in sum xs + length xs

But it causes a change in memory *complexity*, so in some sense these
two sentences are not equal.  What is the theory in which we can
observe this fact?  Is it possible to give a simple denotational
semantics which captures it?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: Haddock version 2.4.0

2008-11-05 Thread David Waern

-- Haddock 2.4.0


A new version of Haddock, the Haskell documentation tool, is out.

This is a later version than the one shipped with GHC 6.10.1, which is version
2.3.0. That version will not be released on Hackage since it only builds with
GHC 6.10.1 (by accident, actually).

Besides adding back support for earlier GHC versions, this release contains
some more fixes and support for HTML frames.

Please use the bug tracker to submit bug reports or feature requests.


-- Changes in version 2.4.0


  * Add framed view of the HTML documentation

  * Build with GHC 6.8.2 and 6.8.3 again

  * Support images in documentation comments again

  * Small improvements to the Hoogle output

  * A few bugs has been fixed


-- Changes in version 2.3.0


  * Support for GHC 6.10.1

  * Slightly improved space usage

  * Fix a bug that made hidden modules show up in the contents & index pages

  * Fix a bug that made Haddock load modules twice

  * Improvements to the Hoogle output


-- Links


Homepage:
 http://www.haskell.org/haddock

Hackage page:
 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/haddock-2.4.0

Bugtracker and wiki:
 http://trac.haskell.org/haddock

Mailing list:
 [EMAIL PROTECTED]

Code repository:
 http://code.haskell.org/haddock


-- Contributors


The persons who contributed to the 2.3.0 and 2.4.0 releases are:

 Clemens Fruhwirth
 Peter Gavin
 Ian Lynagh
 Neil Mitchell
 Luke Plant
 Thomas Schilling
 David Waern


-- Get Involved


We welcome new contributors. To get involved, start by grabbing the code:

 http://code.haskell.org/haddock

Then take a look at the bug and feature tracker for things to work on:

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


Re: [Haskell-cafe] Re: Efficient parallel regular expressions

2008-11-05 Thread Richard O'Keefe


On 6 Nov 2008, at 1:25 am, Johannes Waldmann wrote:

using strings (inside a program) to represent structured data
is wrong (*).


+1

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


Re: [Haskell-cafe] foldl vs foldl'

2008-11-05 Thread Derek Elkins
On Wed, 2008-11-05 at 10:01 -0800, Daryoush Mehrtash wrote:
> Lets assume we don't have undefined in the list, are there functions
> (or properties in the function) that would cause foldl to have
> different results than foldl'?

The only difference in the definition of foldl and foldl' is a seq so it
can only differ due to bottoms as far as semantics is concerned.

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


Re: [Haskell-cafe] view patterns

2008-11-05 Thread Cale Gibbard
2008/11/5 Cetin Sert <[EMAIL PROTECTED]>:
> :1:4:
> Warning: Pattern match(es) are overlapped
>  In the definition of `emp':
>  emp ((has -> True)) = ...
>  emp ((has -> False)) = ...
>
> Why do I get this error in ghc or when I try to compile a file with view
> patterns?
> (using -fglasgow-exts  and -XViewPatterns, ghc 6.10.1)

This is a bug which appears to be known about:
http://hackage.haskell.org/trac/ghc/ticket/2395

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


Re: [Haskell-cafe] Writing an IRC bot, problems with plugins

2008-11-05 Thread Don Stewart
alexanderforemny:
>My general idea is to have the main application listening to the network
>socket and then calling all the plugins on each incoming message.
>Therefore I maintain a list of plugin states in the main application's
>state and on each incoming message I call a function which modifies the
>plugin's state.

Like lambdabot!
  
>There's a PluginClass class which contains definitions of functions for
>each plugin which they all share. Simplyfied it's like this:
> 
>type PL = StateT PluginConfig
> 
>class PluginClass a where
>identifier :: a -> String
>rawMessage :: (MonadIO m) => a -> Message -> PL m ()

Like lambdabot, kind of.
  
>So plugins can be identified uniquely using the identifier function and
>they can respond to messages using the rawMessage function. This function
>is executed in the PL monad, which is essentially a StateT monad for
>updating the plugin's state trough put and maybe accessing a few data
>fields from the underlying Bot monad in which the main application is
>operating.
> 
>Then again I want to be able to query a plugin's state from a different
>plugin. For instance I'll have a plugin which keeps track of the channels
>the bot has joined collecting user information, the topic, etc. Another
>plugin could then query the "chan info" plugin and get all the users in a
>certain channel through a queryPlugin function which takes a plugin and
>looks that plugin up in the main application's plugin state list for the
>right state and then calls a function on it. The plugin and the
>corresponding functions would be exported by the plugin's module.
> 
>queryPlugin :: (PluginClass a) => a -> (a -> b) -> PL m b
>queryPlugin pl f = do
> plugins <- getGlobalPlugins -- ideally (PluginClass a) => [a]
>let pluginNames = map identifier plugins
>targetName = identifier pl
>[(_, target)] = filter ((==) targetName . fst) (zip pluginNames
>plugin)
>return (f target)
> 
>But here I am facing either one or the other problem, depending on the
>"solution."
> 
>1) I somehow have to store all the plugin states in the main application.
>Since plugins are essentially their states, they are quite arbitrary. I
>either cannot use a list for that or I have to use existential types which
>would make that possible.
 
Existential types are used in lambdabot for this. I'd probably use an
associated type to connect the plugin to its state type now, too.


>2) Using an existential plugin type would restrict the functions I am able
>to call on the plugin to those which are supported by the PluginClass.
>This would render queryPlugin unusable since the functions a plugin
>exports for query the state are arbitrary.

You might be able to design around this. Lambdabot manages ok with
existentially typed interfaces.
  

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


Re: [Haskell-cafe] Undefined symbols base_DataziTuple_ZxxxT_con_info

2008-11-05 Thread Bulat Ziganshin
Hello dmitry,

Wednesday, November 5, 2008, 10:46:20 PM, you wrote:

> (.text+0x66dd7):fake: undefined reference to `base_DataziTuple_Z110T_con_info

looks like you omitted --make on cmdline. without this switch, ghc
don't automaticaly links in packages used in you program.
alternatively you may try to use "--package base" (for this case) but
--make is more generic way - it automatically links in all packages
used

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Undefined symbols base_DataziTuple_ZxxxT_con_info

2008-11-05 Thread dmitry shkurko
Hello everyone,

I am trying to compile my program, but during the linking phase I see
errors like:
(.text+0x66dd7):fake: undefined reference to `base_DataziTuple_Z110T_con_info

Library libHSbase.a contains symbols base_DataziTuple_ZxxxT_con_info
for xxx <=62.

It look like I hit some compiler limit (I used GHC 6.8.3 for compilation).

Any thoughts are appreciated.

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


[Haskell-cafe] Strictness problems with Control.Event?

2008-11-05 Thread Brian Troutwine
I'm attempting to use Control.Event to limit HTTP requests made by a
dippy little scraper I'm constructing to once per second but I think,
maybe, that the Events are not being evaluated. First, some imports.

> import qualified Data.ByteString as B
> import qualified Data.ByteString.Char8 as C
> import Network.Curl.Download
> import Network.Curl.Opts
> import System.Exit
> import System.Environment
> import System.Time
> import Control.Event
> import Control.Monad
> import Data.Char

The Event function of this program is append. It takes a local path
and a URL, retrieves the contents pointed to by the URL and appends
them to the local path. The function download, below, performs the
retrieval.

> append :: FilePath -> C.ByteString -> IO ()
> append f u =
> B.appendFile f . addNew . C.filter (not . isAscii) =<< download u
> where addNew = C.append (C.pack "\n")

> download :: B.ByteString -> IO B.ByteString
> download url = do
>   res <- openURIWithOpts [CurlEncoding "gzip", CurlUserAgent "aule-0.0.2"] $ 
> C.unpack url
>   case res of
> Left _ -> exitFailure
> Right cont -> B.putStrLn cont >> return cont

The function sched adds a list of Events to the evtSys system, a fixed
time delay between each.

> sched :: EventSystem -> ClockTime -> Integer -> Integer -> (t -> IO ()) -> 
> [t] -> IO ()
> sched _ _ _ _ _ [] = return ()
> sched evtSys (TOD sec _) delay mul action (x:xs) = do
>   addEvent evtSys (TOD (sec + (delay*mul)) 0) (action x)
>   sched evtSys (TOD sec 0) delay (mul + 1) action xs

main is, as usual, pretty boring. The program compiles and runs, but
no output file is made. This being one of my first appreciable Haskell
programs, I rather imagine I've run into a strictness problem, maybe.
Would someone be so kind as to steer me in the right direction?

> main :: IO ()
> main = do
>   [i, o] <- getArgs
>   eS <- initEventSystem
>   t <- getClockTime
>   inp <- B.readFile i
>   sched eS t 1 1 (append o) (C.lines inp)

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


Re: [Haskell-cafe] pure programs

2008-11-05 Thread Jason Dusek
Jules Bean <[EMAIL PROTECTED]> wrote:
> Jason Dusek wrote:
> > Though that seems reasonable, it is not, in general, true.
> > For example,System.Info.osis generally treated as
> > pure, though it is not. It's not clear to me how to
> > disambiguate  these "born again" values from really pure
> > values.
>
> System.Info is broken. "os" has the wrong type.
>
> Sorry about that. There is quite a lot of brokenness in the
> standard libs which stops pure functions being pure. It's a
> shame IMO.

  I've thought about this a little bit, and it may be okay. What
  if our rule for program purity is a program, once compiled,
  may be moved from environment to environment, and will either
  execute consistently or simply fail to execute. Consider this
  program:

import System.Info

main =  putStrLn os

  If I compile it on Linux and then run the executable on
  FreeBSD, it will either fail to run, because FreeBSD Linux
  compatibility got worse since I tried it last, or run and
  printlinuxas it would on Linux. Does this seem
  reasonable? As long as the programs are statically linked,
  through and through, they should be pure. Admittedly, this
  approach does not address "source level purity", which is
  impossible due to `unsafePerformIO` and, more generally,
  conditional compilation.

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


Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-11-05 Thread Don Stewart
kr.angelov:
> On Wed, Aug 13, 2008 at 1:18 AM, Don Stewart <[EMAIL PROTECTED]> wrote:
> >instance Binary a => Binary [a] where
> >put l  = put (length l) >> mapM_ put l
> >get= do n <- get :: Get Int
> >replicateM n get
> 
> Of course I changed this as well. Now it is:
> 
> instance (Ord k, Binary k, Binary e) => Binary (Map.Map k e) where
> put m = put (Map.size m) >> mapM_ put (Map.toAscList m)
> get   = liftM Map.fromDistinctAscList get
> 
> You don't have to convert the map to list just to compute its size.
> The Map.size is a O(1) function.

If you have a more efficient instance Binary Map, please send a patch.

Collaborate!

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


Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-11-05 Thread Don Stewart
kr.angelov:
> I had the same problem (stack overflow). The solution was to change
> the >>= operator in the Get monad. Currently it is:
> 
>   m >>= k   = Get (\s -> let (a, s') = unGet m s
>in unGet (k a) s')
> 
> but I changed it to:
> 
> m >>= k   = Get (\s -> case unGet m s of
>  (a, s') -> unGet (k a) s')
> 
> It seems that the bind operator is lazy and this caused the stack overflow.

Hmm. That's interesting. I'm not sure that doesn't change other things
we rely on though.
  
> I have also another problem. Every Int and Word is stored as 64-bit
> value and this expands the output file a lot. I have a lot of integers
> and most of them are < 128 but not all of them. I changed the
> serialization so that the Int and Word are serialized in a variable
> number of bytes. Without this change the binary serialization was even
> worse than the textual serialization that we had before. The file was
> almost full with zeros.

The motivation for this is to use zlib compress / decompress.
E.g.

writeFile "f" . compress . encode $ foo
  
> I just haven't time to prepare a patch and to send it for review but
> if other people have the same problem I will do it.
> 

Patches welcome. You shouldn't need to patch a library like this, it
should be able to do what you need.

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


Re: [Haskell-cafe] foldl vs foldl'

2008-11-05 Thread Jonathan Cast
On Wed, 2008-11-05 at 10:01 -0800, Daryoush Mehrtash wrote:
> Lets assume we don't have undefined in the list, are there functions
> (or properties in the function) that would cause foldl to have
> different results than foldl'?

If the function is partial on some elements of the list.

(3 /), for example, if the list contains 0.

If f is total over the elements of the list (whether the elements of the
list are partial or total) and f z /= _|_, then foldl' f z = foldl f z.

jcc


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


Re: [Haskell-cafe] foldl vs foldl'

2008-11-05 Thread Daryoush Mehrtash
Lets assume we don't have undefined in the list, are there functions (or
properties in the function) that would cause foldl to have different results
than foldl'?

daryoush

On Tue, Nov 4, 2008 at 3:37 PM, Daniel Fischer <[EMAIL PROTECTED]>wrote:

> Am Mittwoch, 5. November 2008 00:08 schrieb Daryoush Mehrtash:
> > Are there cases (function or list) where the result of foldl (or
> > foldr)would be different that foldl' (or foldr')?
> >
> > thanks,
> >
> > daryoush
>
> Simple example:
> import Data.List
>
> weird :: Int -> Int -> Int
> weird _ 0 = 0
> weird x y = x*y
>
> list :: [Int]
> list = [1, 2, 3, 4, undefined, 6, 7, 8, 9, 0]
>
> okey = foldl weird 1 list
>
> boom = foldl' weird 1 list
>
> *Main> okey
> 0
> *Main> boom
> *** Exception: Prelude.undefined
>
> since foldl' evaluates strictly (to WHNF), it can die on encountering an
> undefined value in the list where foldl doesn't.
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] HOpenGL wiki link to documentation is broken

2008-11-05 Thread Jefferson Heard
I suspect this has to do with the latest GHC not including it by
default, but the HOpenGL wiki's documentation links are broken.

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


Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-11-05 Thread Krasimir Angelov
I had the same problem (stack overflow). The solution was to change
the >>= operator in the Get monad. Currently it is:

  m >>= k   = Get (\s -> let (a, s') = unGet m s
   in unGet (k a) s')

but I changed it to:

m >>= k   = Get (\s -> case unGet m s of
 (a, s') -> unGet (k a) s')

It seems that the bind operator is lazy and this caused the stack overflow.

I have also another problem. Every Int and Word is stored as 64-bit
value and this expands the output file a lot. I have a lot of integers
and most of them are < 128 but not all of them. I changed the
serialization so that the Int and Word are serialized in a variable
number of bytes. Without this change the binary serialization was even
worse than the textual serialization that we had before. The file was
almost full with zeros.

I just haven't time to prepare a patch and to send it for review but
if other people have the same problem I will do it.


Best Regars,
   Krasimir




On Wed, Aug 13, 2008 at 1:13 AM, Tim Newsham <[EMAIL PROTECTED]> wrote:
> I have a program that read in and populated a large data structure and
> then saved it out with Data.Binary and Data.ByteString.Lazy.Char8:
>
>   saveState db = B.writeFile stateFile =<<
>   encode <$> atomically (readTVar db)
>
> when I go to read this in later I get a stack overflow:
>
> loadState db = do
>d <- decode <$> B.readFile stateFile
>atomically $ writeTVar db d
>
>  Stack space overflow: current size 8388608 bytes.
>  Use `+RTS -Ksize' to increase it.
>
> or from ghci:
>
>d <- liftM decode
>  (Data.ByteString.Lazy.Char8.readFile
> "savedState.bin") :: IO InstrsDb
>
>fromList *** Exception: stack overflow
>
> The data type I'm storing is a Map (of maps):
>
>   type DailyDb = M.Map Date Daily
>   type InstrsDb = M.Map String DailyDb
>
> What's going on here?  Why is the system capable of building and saving
> the data but not in reading and umarhsalling it?  What is the proper way
> to track down where the exception is happening?  Any debugging tips?
>
> I also noticed another issue while testing.  If my program loads
> the data at startup by calling loadState then all later calls to
> saveState give an error:
>
>  Log: savedState.bin: openFile: resource busy (file is locked)
>
> this does not occur if the program wasnt loaded.  My best guess here
> is that B.readFile isnt completing and closing the file for some
> reason.  Is there a good way to force this?
>
> Tim Newsham
> http://www.thenewsh.com/~newsham/
> ___
> 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] Writing an IRC bot, problems with plugins

2008-11-05 Thread Alexander Foremny
Hello, Community.

I already bothered #haskell a few times with the very same problem and
always got interesting responses. But I seem to have always simplified my
problem too much ending up with an helpful answer to my (simplified)
problem, but not with a real solution. Thus I'm giving the mailing list a
try where I don't feel like having to wrap up my concerns in as few lines as
possible.

I am writing an single server, multi channel IRC bot with the support of
plugins and limited plugin communication. With the plugin system I am facing
problems I cannot really solve myself.

My general idea is to have the main application listening to the network
socket and then calling all the plugins on each incoming message. Therefore
I maintain a list of plugin states in the main application's state and on
each incoming message I call a function which modifies the plugin's state.

There's a PluginClass class which contains definitions of functions for each
plugin which they all share. Simplyfied it's like this:

type PL = StateT PluginConfig

class PluginClass a where
identifier :: a -> String
rawMessage :: (MonadIO m) => a -> Message -> PL m ()

So plugins can be identified uniquely using the identifier function and they
can respond to messages using the rawMessage function. This function is
executed in the PL monad, which is essentially a StateT monad for updating
the plugin's state trough put and maybe accessing a few data fields from the
underlying Bot monad in which the main application is operating.

Then again I want to be able to query a plugin's state from a different
plugin. For instance I'll have a plugin which keeps track of the channels
the bot has joined collecting user information, the topic, etc. Another
plugin could then query the "chan info" plugin and get all the users in a
certain channel through a queryPlugin function which takes a plugin and
looks that plugin up in the main application's plugin state list for the
right state and then calls a function on it. The plugin and the
corresponding functions would be exported by the plugin's module.

queryPlugin :: (PluginClass a) => a -> (a -> b) -> PL m b
queryPlugin pl f = do
 plugins <- getGlobalPlugins -- ideally (PluginClass a) => [a]
let pluginNames = map identifier plugins
targetName = identifier pl
[(_, target)] = filter ((==) targetName . fst) (zip pluginNames
plugin)
return (f target)

But here I am facing either one or the other problem, depending on the
"solution."

1) I somehow have to store all the plugin states in the main application.
Since plugins are essentially their states, they are quite arbitrary. I
either cannot use a list for that or I have to use existential types which
would make that possible.

2) Using an existential plugin type would restrict the functions I am able
to call on the plugin to those which are supported by the PluginClass. This
would render queryPlugin unusable since the functions a plugin exports for
query the state are arbitrary.

3) I could use Dynamics to store the plugin in a list *and* call arbitrary
functions, but then again how would I run a plugin? All the main application
know about the plugin state is that all the functions defined by PluginClass
are callable on the state. But the type (PluginClass a) => a isn't enough to
unwrap the Dynamic, apply the function and wrap it again.

Another suggestion was to not use a class but make each plugin a record,
exporting the functions itself. Though I haven't given that a serious
thought, it seems not ideal to me. Using a class a plugin can define the
functions it actually uses. In my real code, they're about 12 functions the
class exports and there could be more. Using a record I would have to
implement all possible functions even though they're not changing the
plugin's state nor causing side effects.

The most obvious solution would be to use an algebraic data type with a
constructor for each plugin. But I'd like to develop the plugins independent
from the core and I'd like to make them more dynamic than that, maybe
implementing dynamic loading of plugins at some time.

Then there are two other potential solutions, but I haven't looked into them
seriously since they seemed a little hackish to me at first glance.
One would be using Hlist (which seems to be over-sized for my problem as
well) and another would be to store a tupel of (Dynamic, (PluginClass a) =>
(Dynamic -> a)) as plugin state list where the first element would be the
plugin's state wrapped in a dynamic and the second a unwrap function
exported by the plugin's module. I *might* get around the problem of being
to unspecific about the type when unwrapping, but this idea came only at the
point of writing this email and I would expect running into the same
problems I have: It can be achieved by either being too general or being to
specific.

Hopefully I've explained everything well enough while not being too long
with all this.

Thanks in advance for your help!
_

Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-11-05 Thread Krasimir Angelov
On Wed, Aug 13, 2008 at 1:18 AM, Don Stewart <[EMAIL PROTECTED]> wrote:
>instance Binary a => Binary [a] where
>put l  = put (length l) >> mapM_ put l
>get= do n <- get :: Get Int
>replicateM n get

Of course I changed this as well. Now it is:

instance (Ord k, Binary k, Binary e) => Binary (Map.Map k e) where
put m = put (Map.size m) >> mapM_ put (Map.toAscList m)
get   = liftM Map.fromDistinctAscList get

You don't have to convert the map to list just to compute its size.
The Map.size is a O(1) function.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-11-05 Thread Ketil Malde
Ketil Malde <[EMAIL PROTECTED]> writes:

> Doing 'x <- decodeFile "/dev/zero"

Well, it turns out 'decodeFile' needs to -- or does, anyway -- check
whether the file is empty.  Replacing it with a combination of
'decode' and 'readFile' solved the problem.

Thanks to Saizan and the other people hanging around on #haskell.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Proposal for associated type synonyms in Template Haskell

2008-11-05 Thread Thomas van Noort

Hello,

Recently, we released a library on Hackage for generic rewriting 
(package "rewriting" if you are curious). The user of the library is 
expected to define type class instances to enable rewriting on his or 
her own datatypes. As these instances follow the datatype declarations 
closely, we tried to generate the instances using Template Haskell. 
Unfortunately, associated type synonyms are not yet supported by TH.


After a presentation at the WGP'08, Simon encouraged us to write a 
proposal about adding associated type synonyms to TH, so that it can be 
added to GHC. So, here is our proposal.


The TH AST must allow 1) kind declarations of associated type synonyms
in class declarations and 2) their definitions in instance declarations. 
For example,


class Foo a where
  type Bar a :: *

instance Foo Int where
  type Bar Int = String

The TH library defines a datatype Dec which contains a constructor for 
class declarations and instance declarations:


data Dec
= ...
| ClassD Cxt Name [Name] [FunDep] [Dec]
| InstanceD Cxt Type [Dec]
  ...

1) Associated type synonym kind declarations

We suggest to add a constructor to the Dec type:

  ...
| AssocTySynKindD Name [Name] (Maybe Kind)
  ...

assocTySynKindD :: Name -> [Name] -> Maybe KindQ -> DecQ

The first field is the name of the associated type synonym, the second 
field is a list of type variables, and the third field is an optional 
kind. Since kinds are not yet defined in TH, we have to add some kind of 
kind definition (pun intended):


data Kind
= StarK
| ArrowK Kind Kind

type KindQ = Q Kind
starK :: KindQ
arrowK :: KindQ -> KindQ -> KindQ

We explicitly choose not to reuse the Type type to define kinds (i.e., 
type Kind = Type as in GHC) since we think a separation between the two 
worlds is much clearer to the users of TH.


2) Associated type synonym definitions

We suggest to add another constructor to the Dec type:

  ...
| AssocTySynD Name [Type] Type
  ...

assocTySynD :: Name -> [TypeQ] -> TypeQ -> DecQ

The first field is the name of the type synonym, the second field is a 
list of type arguments, and the third field is the body of the type synonym.


We would like to hear your comments to this proposal.

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


Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-11-05 Thread Ketil Malde

Old threads never die:

Tim Newsham <[EMAIL PROTECTED]> writes:

>> Chunk = {
>>length :: Word8
>>elems :: [Elem]  --  0..255 repetitions
>>  }
>> Chunks = [Chunk] -- terminated with the first 0 length Chunk

> I tried my hand at the encoding above:
>
> http://www.thenewsh.com/%7Enewsham/store/test10.hs
>
> it seems to work, although it doesn't seem to be very efficient.
> I'm getting very large memory growth when I was hoping it
> would be lazy and memory efficient...  What's leaking?

Did you ever get to the bottom of this?

I have a similar problem with Data.Binary that I don't know how to
work around yet.  It boils down to reading a large list.  This
exhibits the problem:

  newtype Foo = Foo [Word8]
  instance Binary Foo where
  get = do 
xs <- replicateM 1000 get
return (Foo xs)

Doing 'x <- decodeFile "/dev/zero" and "case x of Foo y -> take 10 y"
blows the heap.  I thought Data.Binary was lazy?

My actual program looks something like this:

  instance Binary MyData where
 get = do
 header <- get
 data   <- replicateM (data_length header) $ do 
  stuff to read a data item
 return (MyData header data)

This blows the stack as soon as I try to access anything, even if it's
just the contents of the header.  Why?

My understanding of how Data.Binary works must be sorely lacking.
Could some kind soul please disperse some enlightenment in my
direction? 

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Problems with strictness analysis?

2008-11-05 Thread Achim Schneider
Henning Thielemann <[EMAIL PROTECTED]> wrote:

> Achim Schneider schrieb:
> > Henning Thielemann <[EMAIL PROTECTED]> wrote:
> >>
> >> There was
> >>   http://www.haskell.org/haskellwiki/Things_to_avoid
> >>
> >> which has been renamed to the more friendly
> >>   "Haskell programming tips"
> >>
> > I was rather thinking of a list of performance pitfalls and laziness
> > tarpits, starting with the all-famous
> > 
> > avg xs = sum xs + length xs
> 
> 
> (/) instead of (+) ?
> 
Only for sufficient correct definitions of avg.


-- 
(c) this sig last receiving data processing entity. Inspect headers
for copyright history. All rights reserved. Copying, hiring, renting,
performance and/or quoting of this signature prohibited.


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


[Haskell-cafe] Re: Efficient parallel regular expressions

2008-11-05 Thread Achim Schneider
"roger peppe" <[EMAIL PROTECTED]> wrote:

> On Wed, Nov 5, 2008 at 1:56 PM, Martijn van Steenbergen
> <[EMAIL PROTECTED]> wrote:
> > I think I'll try roger's (private)
> 
> eek, bitten by "reply to sender only" again!
> 
> i had intended to send to the list too.
>
I recommend using a newsreader and connecting it to gmane, you won't
ever have that problem there.

-- 
(c) this sig last receiving data processing entity. Inspect headers
for copyright history. All rights reserved. Copying, hiring, renting,
performance and/or quoting of this signature prohibited.


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


[Haskell-cafe] Re: Problems with strictness analysis?

2008-11-05 Thread Achim Schneider
"Luke Palmer" <[EMAIL PROTECTED]> wrote:

> On Wed, Nov 5, 2008 at 4:33 AM, Achim Schneider <[EMAIL PROTECTED]>
> wrote:
> > I know that I, coming from a C/Scheme POV, in the beginning
> > attributed much magic to Haskell's inner workings and assumed,
> > because of the general wizardly air of the whole language, avg to
> > run in O(n) time and constant resp. O(n) space.
> 
> Haskell's great strength is its equational semantics.  I would like
> Haskell programmers to think equationally, mathematically, rather than
> operationally, when writing Haskell programs.  If I were to teach a
> course in Haskell, I would like to launch off of denotational
> semantics, hopefully without ever having to say "lazy evaluation".
> (It's a pipe dream, of course, but you get the idea)
> 
> However, this strength is also a weakness when we want to analyze the
> efficiency of programs.  The denotational semantics of Haskell say
> nothing about time or space complexity, and give us no tools to reason
> about it.  A Haskell interpreter which randomly rewrites terms until
> it happens upon a normal form is considered correct (or rather,
> "correct with probability 1" :-).
> 
> How can we support analysis of time and space complexity without
> expanding ourselves into the complicated dirty world of operational
> thinking?
> 
You can't clean a student's mind from "bad, dirty operational thoughts"
by not talking about it as much as you can't exterminate the human race
by discontinuing sexual education. Fumbling the keyboard and making
things go "blink" and "swoosh" is just too much fun.

A natural understanding of what's "clean, elegant and fun" develops
over time, and students have to rub their nose into gory and dirty
details and code until it bleeds before they see what all that
abstract nonsense is good for: Not so much to formalise thinking, but
to enable one to speak axiomatically, just like one thinks.  

-- 
(c) this sig last receiving data processing entity. Inspect headers
for copyright history. All rights reserved. Copying, hiring, renting,
performance and/or quoting of this signature prohibited.


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


Re: [Haskell-cafe] Re: Efficient parallel regular expressions

2008-11-05 Thread Henning Thielemann
Johannes Waldmann schrieb:
> using strings (inside a program) to represent structured data
> is wrong (*). 
> 
> of course you need strings for interfacing the "outside" world, 
> but the microsecond they get on the inside,
> they should be tokenized and parsed away
> into something useful (= an abstract syntax tree).
>  
> (*) corollary: 
> using strings to represent regular expressions is also wrong...

I consider these regular expression strings an embedded domain-specific
language. It seems to me, that putting regexps into strings was a
work-around, because you could not extend Haskell's syntax. But now
things change with this new GHC feature - what was its name?
Nevertheless, I never used regexps in Haskell programs, parsec is much
nicer.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Efficient parallel regular expressions

2008-11-05 Thread roger peppe
On Wed, Nov 5, 2008 at 1:56 PM, Martijn van Steenbergen
<[EMAIL PROTECTED]> wrote:
> I think I'll try roger's (private)

eek, bitten by "reply to sender only" again!

i had intended to send to the list too.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Efficient parallel regular expressions

2008-11-05 Thread roger peppe
On Tue, Nov 4, 2008 at 6:44 PM, i wrote:
> i'm sorry if this is obviously wrong (i haven't used Text.Regex), but
> can't you do this with submatches?

rights or wrongs of regexps aside, i just checked that the above
approach *is* feasible with Text.Regex

here's some code:

>module Multimatch(multimatch) where
>   import Text.Regex
>   import qualified Data.List as DL
>   import qualified Data.Maybe as DM
>
>   brcount :: String -> Int
>   brcount ('\\' : _ : s) =
>   brcount s
>   brcount ('(' : s) =
>   1 + brcount s
>   brcount (_ : s) =
>   brcount s
>   brcount [] =
>   0
>
>   -- given a list of strings representing regular expressions,
>   -- each associated with a tag, match against a string
>   -- and return the match, along with the associated tag,
>   -- or Nothing if there's no match.
>   multimatch :: [(tag, String)] -> (String -> Maybe (tag, String))
>   multimatch rs =
>   let re = mkRegex $ DL.intercalate "|" $ map ((\s -> "(x(" ++ s 
> ++ "))") . snd) rs in
>   let tags = submatches rs in
>   (\ s ->
>   do
>   ms <- matchRegex re ("x" ++ s)
>   (tag, m) <- DL.find (\(_, m) -> not (null m)) 
> (zip tags ms)
>   return (DM.fromJust tag, tail m))
>   submatches [] =
>   []
>   submatches ((tag, r) : rs) =
>   (Just tag : take (brcount r + 1) (repeat Nothing)) ++ 
> submatches rs

i'm sure there's a more compact implementation in there somewhere:
i'm just a haskell newbie.

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


Re: [Haskell-cafe] Re: Problems with strictness analysis?

2008-11-05 Thread Henning Thielemann
Achim Schneider schrieb:
> Henning Thielemann <[EMAIL PROTECTED]> wrote:
>>
>> There was
>>   http://www.haskell.org/haskellwiki/Things_to_avoid
>>
>> which has been renamed to the more friendly
>>   "Haskell programming tips"
>>
> I was rather thinking of a list of performance pitfalls and laziness
> tarpits, starting with the all-famous
> 
> avg xs = sum xs + length xs


(/) instead of (+) ?

In the old hawiki there was an article about that particular example ...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Efficient parallel regular expressions

2008-11-05 Thread Martijn van Steenbergen

Hello everyone,

Thank you all for your comments! Those are some very useful ideas.

I think I'll try roger's (private) and ChrisK's suggestion first: using 
the match groups. I'm not sure if the match groups inside the individual 
 regexes will cause much trouble, but we'll see. I imagine I'll have to 
count parentheses, except when it's followed by a \, except when that \ 
follows another \, etc. There's probably other situations where a () 
doesn't count as a group, perhaps when it's followed by a * or +. I'll 
look into that.


If that doesn't work out I'll go for Neil's (from an algorithmic POV 
beautiful) suggestion.


While I understand that some of you suggest I use parsec (or some other 
mature parser library) I'm pretty sure that's not what I want here. The 
patterns will almost always be very simple and regular expressions offer 
an extremely concise way of expressing when a hook should fire. Forcing 
the user to use full parsers would cause the programs to become much 
more verbose. Still, Yogurt is flexible enough to allow the user to use 
parsec if he or she so chooses.


Thanks again,

Martijn.



Mitchell, Neil wrote:

Hi Martijn,

It's not that tricky if you do a regular expression state machine
yourself, but that's probably a bit too much work. One way to get a
speed up might be to take the regular expressions a,b,c,d and
generate a regex a+b+c+d, and one a+b. You can then check any string
s against a+b+c+d, if that matches check a+b, if that matches check
a. At each stage you eliminate half the regular expressions, which
means a match will take log n, where n is the number of regular
expressions.

This assumes the underlying regular expression engine constructs a
finite state machine, making it O(m) where m is the length of the
string to match.

Thanks

Neil

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


[Haskell-cafe] Re: Efficient parallel regular expressions

2008-11-05 Thread Johannes Waldmann

using strings (inside a program) to represent structured data
is wrong (*). 

of course you need strings for interfacing the "outside" world, 
but the microsecond they get on the inside,
they should be tokenized and parsed away
into something useful (= an abstract syntax tree).
 
(*) corollary: 
using strings to represent regular expressions is also wrong...




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


Re: [Haskell-cafe] Re: Problems with strictness analysis?

2008-11-05 Thread Claus Reinke

Haskell's great strength is its equational semantics.  I would like
Haskell programmers to think equationally, mathematically, rather than
operationally, when writing Haskell programs.  If I were to teach a
course in Haskell, I would like to launch off of denotational
semantics, hopefully without ever having to say "lazy evaluation".
(It's a pipe dream, of course, but you get the idea)

However, this strength is also a weakness when we want to analyze the
efficiency of programs.  The denotational semantics of Haskell say
nothing about time or space complexity, and give us no tools to reason
about it.  A Haskell interpreter which randomly rewrites terms until
it happens upon a normal form is considered correct (or rather,
"correct with probability 1" :-).

How can we support analysis of time and space complexity without
expanding ourselves into the complicated dirty world of operational
thinking?


   equational /= denotational
   operational /= bad

Sometimes, denotational is too abstract, offering no guidelines on behaviour, 
just as abstract machine based operational thinking is too concrete, hiding
the insights in a flood of details. Sometimes, operational semantics based 
on directed equations give you the best of both worlds: equational reasoning 
and behavioural guidelines, both at a suitably "clean" and abstract level.


Claus

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


Re: [Haskell-cafe] foldl vs foldl'

2008-11-05 Thread Nicolas Pouillard
Excerpts from daniel.is.fischer's message of Wed Nov 05 00:37:47 +0100 2008:
> Am Mittwoch, 5. November 2008 00:08 schrieb Daryoush Mehrtash:
> > Are there cases (function or list) where the result of foldl (or
> > foldr)would be different that foldl' (or foldr')?
> >
> > thanks,
> >
> > daryoush
> 
> Simple example:
> import Data.List
> 
> weird :: Int -> Int -> Int
> weird _ 0 = 0
> weird x y = x*y
> 
> list :: [Int]
> list = [1, 2, 3, 4, undefined, 6, 7, 8, 9, 0]
> 
> okey = foldl weird 1 list
> 
> boom = foldl' weird 1 list
> 
> *Main> okey
> 0
> *Main> boom
> *** Exception: Prelude.undefined
> 
> since foldl' evaluates strictly (to WHNF), it can die on encountering an 
> undefined value in the list where foldl doesn't.

Your example is a nice example of foldl over foldl', it would be nice to have it
in the wiki page about the different folds[1].

Best regards,

[1]: http://haskell.org/haskellwiki/Foldr_Foldl_Foldl%27

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


Re: [Haskell-cafe] Re: Efficient parallel regular expressions

2008-11-05 Thread Nicolas Pouillard
Excerpts from ajb's message of Wed Nov 05 03:59:03 +0100 2008:
> G'day all.

Hi,

> 
> Quoting Achim Schneider <[EMAIL PROTECTED]>:
> 
> > Considering that he's talking about a mud, I figure the grammar is a
> > quite straightforward
> >
> > command = l[eft] | r[ight] | ... | t[ake]  | c[ast] 
> >
> > That is, I'd be very surprised if you even need more than two or three
> > characters lookahead, much less backtracking.
> 
> In the case of a command followed by arguments, it would make more
> sense to use a keyword recogniser followed by a command-specific parser.
> 
> One suggestion follows.

Oops there is a bug in there:

GHCI> keywordMatch  [("a", 1), ("aa", 2)] "aa"
Nothing

The third equation of generateTrie' is missing a guard, namely k1 /= k2.

generateTrie' [(k1:ks1,v1),(k2:ks2,v2)] | k1 /= k2
 = Node2 k1 (generateTrie [(ks1,v1)]) k2 (generateTrie [(ks2,v2)])

Best regards,

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


Re: [Haskell-cafe] Re: Problems with strictness analysis?

2008-11-05 Thread Luke Palmer
On Wed, Nov 5, 2008 at 4:33 AM, Achim Schneider <[EMAIL PROTECTED]> wrote:
> I know that I, coming from a C/Scheme POV, in the beginning attributed
> much magic to Haskell's inner workings and assumed, because of the
> general wizardly air of the whole language, avg to run in O(n) time and
> constant resp. O(n) space.

Haskell's great strength is its equational semantics.  I would like
Haskell programmers to think equationally, mathematically, rather than
operationally, when writing Haskell programs.  If I were to teach a
course in Haskell, I would like to launch off of denotational
semantics, hopefully without ever having to say "lazy evaluation".
(It's a pipe dream, of course, but you get the idea)

However, this strength is also a weakness when we want to analyze the
efficiency of programs.  The denotational semantics of Haskell say
nothing about time or space complexity, and give us no tools to reason
about it.  A Haskell interpreter which randomly rewrites terms until
it happens upon a normal form is considered correct (or rather,
"correct with probability 1" :-).

How can we support analysis of time and space complexity without
expanding ourselves into the complicated dirty world of operational
thinking?

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


[Haskell-cafe] Re: Problems with strictness analysis?

2008-11-05 Thread Achim Schneider
Henning Thielemann <[EMAIL PROTECTED]> wrote:

> Achim Schneider schrieb:
> > Derek Elkins <[EMAIL PROTECTED]> wrote:
> > 
> >> well-known anti-patterns
> >>
> > I'm wondering why there are so miraculously well-known. Could it be
> > the dedicated wiki page titled "DONTDOTHAT!!!one!" that lists them
> > all?
> 
> 
> There was
>   http://www.haskell.org/haskellwiki/Things_to_avoid
> 
> which has been renamed to the more friendly
>   "Haskell programming tips"
>
I was rather thinking of a list of performance pitfalls and laziness
tarpits, starting with the all-famous

avg xs = sum xs + length xs

The above link seems to consist purely of advice about style and how to
avoid imperative thinking, and does not do much to take the fear out of
FP and laziness I commonly notice in e.g. C++ programmers: Seeing
Haskell, they just don't know what the heck is going on. A list of such
things like avg above and stuff like

lastInt = last [1..]

and explanations on why and how they work (and maybe still don't work)
would surely be helpful for people who don't intend or don't even
start to consider to read into SPJ's GHC papers.

I know that I, coming from a C/Scheme POV, in the beginning attributed
much magic to Haskell's inner workings and assumed, because of the
general wizardly air of the whole language, avg to run in O(n) time and
constant resp. O(n) space.

-- 
(c) this sig last receiving data processing entity. Inspect headers
for copyright history. All rights reserved. Copying, hiring, renting,
performance and/or quoting of this signature prohibited.


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


RE: [Haskell-cafe] pure programs

2008-11-05 Thread Mitchell, Neil

> System.Info is broken. "os" has the wrong type.

And the wrong value!

I have not installed mingw32 on this machine, mingw32 isn't even an
os...

/me has goal of having "os" on Linux report "wine1.1.7"

Thanks

Neil

==
Please access the attached hyperlink for an important electronic communications 
disclaimer: 

http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
==

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


Re: [Haskell-cafe] pure programs

2008-11-05 Thread Jules Bean

Jason Dusek wrote:

  Though that seems reasonable, it is not, in general, true. For
  example,System.Info.osis generally treated as pure,
  though it is not. It's not clear to me how to disambiguate
  these "born again" values from really pure values.


It seems to me no one addressed your actual point.

System.Info is broken. "os" has the wrong type.

Sorry about that. There is quite a lot of brokenness in the standard 
libs which stops pure functions being pure. It's a shame IMO.


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


Re: [Haskell-cafe] Re: Problems with strictness analysis?

2008-11-05 Thread Henning Thielemann
Achim Schneider schrieb:
> Derek Elkins <[EMAIL PROTECTED]> wrote:
> 
>> well-known anti-patterns
>>
> I'm wondering why there are so miraculously well-known. Could it be the
> dedicated wiki page titled "DONTDOTHAT!!!one!" that lists them
> all?


There was
  http://www.haskell.org/haskellwiki/Things_to_avoid

which has been renamed to the more friendly
  "Haskell programming tips"
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Automatic parallelism in Haskell, similar to "make -j4"?

2008-11-05 Thread Austin Seipp
Excerpts from Chad Scherrer's message of Tue Nov 04 21:34:01 -0600 2008:
> Does anyone have any thought what it would take to get this going?
> 
> Chad
> 

Currently, franchise supports building in parallel with a -j flag, but
the code could definitely be optimized (in my experience, running with
something like -j3 on my dual core reduces compile times with
franchise on arbitrary projects about 20% currently.) During the 2008
SOC, there was also work on adding this support to cabal, which
eventually ended up as the hbuild project.

http://hackage.haskell.org/trac/hackage/wiki/HBuild

darcs get http://darcs.net/repos/franchise

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


RE: [Haskell-cafe] Memory efficiency questions for real-time graphics

2008-11-05 Thread Tobias Bexelius
I believe Svein is thinking of render-to-texture which indeed could be
used to emulate Stream-Out functionality (but with reduced performance
of course). This is also hardware specific and was still not supported
on the first GPU's.

 


From: Sebastian Sylvan [mailto:[EMAIL PROTECTED] 
Sent: den 4 november 2008 20:06
To: [EMAIL PROTECTED]
Cc: Tobias Bexelius; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Memory efficiency questions for real-time
graphics




On Mon, Nov 3, 2008 at 3:45 PM, Svein Ove Aas <[EMAIL PROTECTED]> wrote:


On Mon, Nov 3, 2008 at 11:31 AM, Tobias Bexelius
<[EMAIL PROTECTED]> wrote:
> Before Direct3D 10, its too costly to read back the updated
vertex data
> in every frame, which force you to make this kind of
operations on the
> CPU.
> With D3D 10 however, you should use the new Stream-Output
stage which is
> used to return updated vertex data directly to a vertex buffer
on the
> GPU. So if you can afford a new graphics card and likes Vista,
that's
> the way to go :)
>

Or you could use OpenGL, which has supported that since the
first GPUs
that did were released.


I think that came with OpenGL 3.0. Unless you're counting
vendor-specific extensions... 

-- 
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862

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


[Haskell-cafe] Re: pure programs

2008-11-05 Thread Achim Schneider
"Jason Dusek" <[EMAIL PROTECTED]> wrote:

> Can these components can
>   be Haskell functions without IO in their signatures?
>
Sure. You might, for example, abstract networking out of your web
server and thus end up with a function of type

serve :: [HTTPRequest] -> [HTTPResponse]

that lazily maps its input stream to an output stream. You can keep
state by passing your state to yourself in a recursive call or do
something more involved like using the state monad, but you'll find it
very, very, very hard to write a genuinely non-deterministic program
without changing input data, no matter what you do, even on
multiprocessors.

Enabling such things seems rather to be the scope of INTERCAL... does
it already have a MAYBE COME FROM statement that relies on an external
random source?

-- 
(c) this sig last receiving data processing entity. Inspect headers
for copyright history. All rights reserved. Copying, hiring, renting,
performance and/or quoting of this signature prohibited.


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


[Haskell-cafe] Re: Problems with strictness analysis?

2008-11-05 Thread Achim Schneider
Derek Elkins <[EMAIL PROTECTED]> wrote:

> well-known anti-patterns
>
I'm wondering why there are so miraculously well-known. Could it be the
dedicated wiki page titled "DONTDOTHAT!!!one!" that lists them
all?

-- 
(c) this sig last receiving data processing entity. Inspect headers
for copyright history. All rights reserved. Copying, hiring, renting,
performance and/or quoting of this signature prohibited.


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


Re: [Haskell-cafe] pure programs

2008-11-05 Thread Alberto G. Corona
A performance improvement could be the caching of responses based on
computation costs and number of accesses. This functionality can be
implemented a general module that may be used to wrap any pure program if
needed. This is something that only pure programs can ever do. And the
haskell type system can enforce that.

2008/11/5 Bulat Ziganshin <[EMAIL PROTECTED]>

> Hello Jason,
>
> Wednesday, November 5, 2008, 3:12:29 AM, you wrote:
>
> >   Many useful programs that I would like to write in Haskell
> >   don't fall into this category -- for example, network servers
> >   -- but a lot of their components do. Can these components can
> >   be Haskell functions without IO in their signatures?
>
> pure function is one those result depends only on its arguments. as
> far as you can provide "input stream" as an function argument, it
> should be possible to write it in pure way (as far as you don't
> concern efficiency. sometimes imperative algorithms mauy be just
> faster than pure ones since data structures are different)
>
>
> --
> Best regards,
>  Bulatmailto:[EMAIL PROTECTED]
>
> ___
> 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] Making 'community' server our social network

2008-11-05 Thread Wolfgang Jeltsch
Am Montag, 3. November 2008 02:43 schrieb Maurí­cio:
> Hi,
>
> I've  beeing doing  something with  darcs that  is so  great that,
> although I'm  sure a lot of  people are already doing  the same, I
> think it would be nice to share with you. I did 'cd ~' and then:
>
> darcs initialize
> darcs add .emacs
> darcs add .xmonad/xmonad.hs
> darcs add .inputrc
> ...
> etc.
>
> So I'm  using darcs to keep  track of all my  configuration files,
> and now I  don't need to care about reinstalling  the OS, changing
> machines  from office  to home,  changing configurations  and then
> realizing it was a mistake etc.
>
> Then I  thought community.haskell.org could offer  a default darcs
> repositories for all users named after their owners. For instance,
> if you want to check my personal files you would do:
>
> darcs get http://code.haskell.org/MauricioAntunes
>
> That would allow us not only  to share our configuration, but also
> share all  those small  files that  are not  "professional" enough
> to  became  projects for  their  own,  but that  are  nevertheless
> interesting since  we put our  good ideas there: scripts  to start
> our  favorite software  or  do system  maintenance; small  Haskell
> utilities  to do  some cool  math  or science  trick, stress  some
> language feature  or download  our standard music  collection from
> the web;  a list of favorite  sites and a related completion script
> so we can list then in 'dmenu' completion; etc. etc. etc.
>
> The next bonus  step would be to  get a list at  all users default
> repository main  page of all  other users they have  granted write
> access  to some  of  their  projects. Then  we  would  be able  to
> navigate throw linked  lists of people with  related interests and
> needs.
>
> I think we need  no more to get what will  be MySpace, Facebook or
> something else for text-driven people.  And then, of course, world
> domination.  Although I  don't really  imagine any  business model
> around that :)
>
> Best,
> Maurício

So your idea means that I have to store all my configuration files etc. in a 
single darcs repository?  Not a nice idea, in my opinion.  I already use 
darcs for synchronizing data between my work and home computer but I use 
several repositories for several topics.  A topic would be something like a 
lecture I write exercises for or a conference I write a paper for.

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


Re: [Haskell-cafe] Efficient parallel regular expressions

2008-11-05 Thread Krasimir Angelov
Hi Martijn,

If you are brave to start implementing DFA with all required
optimisations then you might want to look at:

http://www.ontotext.com/gate/japec.html

This is a compiler for language called JAPE. In the language you
define a set of rules where the right hand side
is a regular expression and the left hand side is a Java code. The
compiler itself is implemented in Haskell.
It includes code to build DFA from the set of regexps and then it does
determinization and minimization.

I wrote the compiler few years ago. You can decide to take and change
the code or to reimplement it yourself. Definitely DFA guarantees that
the performance is always linear while with Parsec you have to be
careful.

Regards,
   Krasimir



On Tue, Nov 4, 2008 at 6:05 PM, Martijn van Steenbergen
<[EMAIL PROTECTED]> wrote:
> Hello all,
>
> For my mud client Yogurt (see hackage) I'm currently working on
> improving the efficiency of the hooks. Right now several hooks, each
> consisting of a regex and an action can be active at the same time.
> Every time a line of input is available (usually several times a second)
> I run the line through all the available regexes and execute the first
> matching action.
>
> I figured this is not the cleverest approach and it'd be better if I
> |'ed all regexes into one big DFA. However, how do I then find out which
> of the original hooks matched and so which action to execute?
>
> As far as I know there's no way to do that with Text.Regex. Alex looks
> promising but is really only an executable and doesn't offer an API.
> I've also found mr. João Saraiva's HaLex but I don't know if that was
> meant to be used seriously.
>
> Does anyone have any experience with this? What's the best way to
> achieve this?
>
> Thanks much,
>
> Martijn.
>
> ___
> 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