Re: [Haskell-cafe] Safe Haskell and instance coherence

2012-10-17 Thread Mikhail Glushenkov
Hello David,

On Thu, Oct 18, 2012 at 6:21 AM, David Mazieres expires 2013-01-15 PST

wrote:
>
> What's interesting is that these examples doesn't violate the goals of
> Safe Haskell--i.e., they don't violate type safety, encapsulation, or
> semantic consistency as we defined it--but they are worrisome.

I think that my example violates encapsulation in a similar way to how
GND violates encapsulation in the MinList example from the Safe
Haskell paper.

IIUC, the problem is that all instances are assumed to be coherent
(that's why it's an error to have two Monoid Int instances in the same
module), but this assumption isn't actually enforced across module
boundaries, even though it is reflected in the type system. GHC does
print a warning after having encountered orphan instances, but that's
all.

> This is essentially the same thing as my Monoid example.  You've got
> two different dictionaries for the same type, and can pass either one
> around depending on what module you imported.

Are "dictionaries" something that is a part of Haskell semantics or an
artefact of the implementation?

> It's
> not hard to cook up a contrived example where some sort of security
> monitor hands over the keys to the kingdom if ever it encounters
> duplicate items in a set.  Auditing the code, that might seem fine
> unless you understand the implementation of Set, which makes reasoning
> about security a lot harder.

Agreed.

> What we really want is for the dictionary to be associated with the
> data structure at the time of creation, not passed in as an argument
> for each operation.  But that's not even implementable without the
> existential types extension, and also would require re-writing all the
> containers, which is absolutely not what we want.

This is what Scala does. Unfortunately, this can make some operations
(e.g. set union) asymptotically less efficient (as it's now impossible
to rely on the fact that both sets use the same associated
dictionary).

> Failing that, I guess we could disallow overlapping instances even
> when they don't overlap in a single module.  This is a whole-program
> check similar to what type families requires, so could possibly be
> implemented in a similar way.

I'm really interested in the link-time check that is performed for
type families. Is it described somewhere?

> However, as with type families, making
> it work with dynamic loading is going to be kind of hard.  Essentially
> there would have to be some run-time inspectable information about all
> instances defined.

I think that's why Rust chose to just disallow orphan instances :-)
Even without dynamic loading, supporting all GHC extensions (e.g.
FlexibleInstances) will probably be non-trivial.


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

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


Re: [Haskell-cafe] generalizing the writer monad

2012-10-17 Thread Strake
 On 17/10/2012, Petr P  wrote:
> Hi,
>
> (this is a literate Haskell post.)
>
> lately I was playing with the Writer monad and it seems to me that it
> is too tightly coupled with monoids. Currently, MonadWriter makes the
> following assumptions:
>
> (1) The written value can be read again later.
> (2) For that to be possible it has to be monoid so that multiple (or
> zero) values can be combined.
>
> I fell say that this is a bit restricting. Sometimes, the written
> value can be lost - either used to compute something else or for
> example sent out using some IO action to a file, network etc. For
> example, I'd like to create an IO-based writer monad whose `tell` logs
> its argument somewhere - prints it, stores to a file etc.

No need:

newtype SequenceM m a = SequenceM (m a);

instance (Monad m, Monoid a) => Monoid (SequenceM m a) where {
  mempty = SequenceM (return mempty);
  SequenceM mx `mappend` SequenceM my = SequenceM (liftM2 mappend mx my);
}

whatever :: (MonadWriter (SequenceM IO ()) m) => m ();
whatever = tell (SequenceM (someIO :: IO ()));

Cheers,
Strake

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


Re: [Haskell-cafe] Solving integer equations in Haskell

2012-10-17 Thread John D. Ramsdell
For Linear integer equations, I think you want

http://hackage.haskell.org/packages/archive/agum/2.4/doc/html/Algebra-AbelianGroup-IntLinEq.html

The algorithm used to find solutions is described in Vol. 2 of The Art
of Computer Programming / Seminumerical Alorithms, 2nd Ed., 1981, by
Donald E. Knuth, pg. 327.

John

On Mon, Oct 15, 2012 at 10:39 PM, Levent Erkok  wrote:
> On Mon, Oct 15, 2012 at 9:00 AM, Johannes Waldmann
>  wrote:
>> Justin Paston-Cooper  gmail.com> writes:
>>
>>> Can anyone suggest a library written in Haskell which can solve equations
>>> of the form xM(transpose(x)) = y, where x should be an integer vector,
>>> M is an integer matrix and y is an integer?
>>
>> when in doubt, use brute force:
>>
>> write this as a constraint system
>> (in QF_NIA or QF_BV logics) and solve with Z3.
>
> As Johannes mentioned, you can indeed use SBV/Z3 to solve such
> problems. Indeed, there's an existing example for showing how to solve
> Diophantine equations this way:
>
>   
> http://hackage.haskell.org/packages/archive/sbv/2.3/doc/html/Data-SBV-Examples-Existentials-Diophantine.html
>
> The technique described there can be used to solve the problem you've
> described; or systems of arbitrary constraint equations in general
> with minor tweaks.
>
> Having said that, using an SMT solver for this problem may not
> necessarily be the fastest route. The general purpose nature of SMT
> solving, while sound and complete for this class of problems, are not
> necessarily the most efficient when there are existing fast
> algorithms. In particular, you should check out John Ramsdell's cmu
> package: http://hackage.haskell.org/package/cmu. In particular see:
>
> 
> http://hackage.haskell.org/packages/archive/cmu/1.8/doc/html/Algebra-CommutativeMonoid-LinDiophEq.html
>
> While the approach here only applies to linear diophantine equations,
> you might be able to adapt it to your particular needs.
>
> -Levent.
>
> ___
> 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] Safe Haskell and instance coherence

2012-10-17 Thread Mikhail Glushenkov
Hello David,

On Wed, Oct 17, 2012 at 6:02 PM, David Mazieres expires 2013-01-15 PST

wrote:
> Can you elaborate on how this can be used to break the data structure
> invariant?  If in safe Haskell you import two modules that have
> overlapping instances, you will not be able to use the two instances.
> Modules that import only one instance will be able to use that
> instance.

Please take a look at the code example I provided:

https://gist.github.com/3854294

I don't use overlapping instances or any other extensions besides Safe
Haskell. By defining two orphan Ord instances for U I'm able to
construct a value of type Set U that contains two equal elements:

> test
fromList [X,Y,X]

This is what I meant by "breaking the data structure invariant". This
shouldn't normally be possible: the documentation for Data.Set.insert
says: "If the set already contains an element equal to the given
value, it is replaced with the new value."

Regarding your Monoid example, it will still be possible to make it
work even if instance coherence is enforced by using a newtype wrapper
(in fact, Data.Monoid already includes Sum and Product newtype
wrappers that provide this functionality).



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

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


[Haskell-cafe] Erroneous interaction between DataKinds and ExistentialQuantification?

2012-10-17 Thread Stefan Holdermans
I am almost sure this is a known issue, but I noticed some erroneous (?) 
interaction between datatype promotion and existential quantification. Consider 
the following program:

  {-# LANGUAGE DataKinds #-}
  {-# LANGUAGE ExistentialQuantification #-}
  {-# LANGUAGE GADTs #-}
  {-# LANGUAGE KindSignatures#-}

  module Test where

  data K = forall a. T a  -- promotion gives 'T :: * -> K   
   

  data G :: K -> * where
D :: G (T []) -- kind error!

I would expect the type checker to reject it, but GHC (version 7.6.1) compiles 
it happily. Is this indeed a (known) bug?

On a related note: is there a way to promote a type that involves an 
existential type variable of a kind other than *?

Thanks,

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


Re: [Haskell-cafe] generalizing the writer monad

2012-10-17 Thread Chris Wong
Hello!

On Thu, Oct 18, 2012 at 6:59 AM, Petr P  wrote:
> Hi,
>
> (this is a literate Haskell post.)
>
> lately I was playing with the Writer monad and it seems to me that it
> is too tightly coupled with monoids. Currently, MonadWriter makes the
> following assumptions:
>
> (1) The written value can be read again later.
> (2) For that to be possible it has to be monoid so that multiple (or
> zero) values can be combined.
>
> I fell say that this is a bit restricting. Sometimes, the written
> value can be lost - either used to compute something else or for
> example sent out using some IO action to a file, network etc. For
> example, I'd like to create an IO-based writer monad whose `tell` logs
> its argument somewhere - prints it, stores to a file etc.

Try the Coroutine monad transformer:

http://hackage.haskell.org/package/monad-coroutine

Instead of writing the log inside the monad, you can yield the message
instead. The calling code is then free to choose what to do with the
messages.

> So what I'm suggesting is to have another type class between Monad and
> MonadWriter, let's say MonadTell, which only allows to write values,
> not to retrieve them later:
>
>> {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, 
>> FunctionalDependencies #-}
>> import Control.Monad
>> import Control.Monad.Trans
>> import qualified Control.Monad.Writer as W
>> import qualified Control.Monad.Reader as R
>> import Data.Monoid
>>
>> class Monad m => MonadTell w m where
>> tell :: w -> m ()
>> tell w = writer ((), w)
>> writer :: (a, w) -> m a
>> writer ~(a, w) = tell w >> return a
>
> (We don't need fun.deps. here, they're needed in MonadWriter because
> of `listen`. IDK if it'd be still better to add fun.dep. just to
> eliminate typing problems?)
>
> And MonadWriter would be defined by inheriting from MonadTell:
>
>> class (MonadTell w m, Monoid w) => MonadWriter' w m | m -> w where
>> listen :: m a -> m (a, w)
>> pass :: m (a, w -> w) -> m a
>
> Now we could use MonadWriter as before, but we could also make more
> generic writers like:
>
>> newtype Log = Log String deriving Show
>> -- Prints logs to stdout.
>> instance MonadTell Log IO where
>> tell (Log s) = putStrLn s
>>
>> -- Collects the length of written logs.
>> instance Monad m => MonadTell Log (W.WriterT (Sum Int) m) where
>> tell (Log s) = W.tell (Sum $ length s)
>>
>>
>> main = do
>> let l = Log "Hello world"
>> tell l
>> print . getSum . W.execWriter $ (tell l :: W.Writer (Sum Int) ())
>
> The same applies to MonadReader. We could make another type class
> between Monad and MonadReader just with `ask`:
>
>> class Monad m => MonadAsk r m | m -> r where
>> ask :: m r
>
> This would allow us to write instances like
>
>> instance MonadAsk Log IO where
>> ask = liftM Log getLine
>
> Does it make sense?
>
> Best regards,
> Petr Pudlak
>
> ___
> 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] poor performance when generating random text

2012-10-17 Thread Alfredo Di Napoli
Glad to have been helpful :)

Bests,
Alfredo

Sent from my iPad

On 17/ott/2012, at 21:10, Dmitry Vyal  wrote:

> On 10/17/2012 12:45 PM, Alfredo Di Napoli wrote:
>> What about this? I've tested on my pc and seems pretty fast. The trick is to 
>> generate the gen only once. Not sure if the inlines helps, though:
>> 
> 
> > What about this? I've tested on my pc and seems pretty fast. The trick is 
> > to generate the gen only once. Not sure if the inlines helps, though
> ...
> 
> Wow, haskell-cafe is a wonderful place! In just a two hours program run time 
> automagically improved 20x ;) Thanks Alfredo, code works wonderful. Compared 
> to mine implementation it's 2.5 sec vs 50 sec on my laptop. Interesting, how 
> it compares to C now.
> 
> Inlining makes about 50x difference when code compiled without optimization. 
> A nice example.
> 
> Best wishes,
> Dmitry
> 

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


Re: [Haskell-cafe] poor performance when generating random text

2012-10-17 Thread Dmitry Vyal

On 10/17/2012 12:45 PM, Alfredo Di Napoli wrote:
What about this? I've tested on my pc and seems pretty fast. The trick 
is to generate the gen only once. Not sure if the inlines helps, though:




> What about this? I've tested on my pc and seems pretty fast. The 
trick is to generate the gen only once. Not sure if the inlines helps, 
though

...

Wow, haskell-cafe is a wonderful place! In just a two hours program run 
time automagically improved 20x ;) Thanks Alfredo, code works wonderful. 
Compared to mine implementation it's 2.5 sec vs 50 sec on my laptop. 
Interesting, how it compares to C now.


Inlining makes about 50x difference when code compiled without 
optimization. A nice example.


Best wishes,
Dmitry


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


[Haskell-cafe] generalizing the writer monad

2012-10-17 Thread Petr P
Hi,

(this is a literate Haskell post.)

lately I was playing with the Writer monad and it seems to me that it
is too tightly coupled with monoids. Currently, MonadWriter makes the
following assumptions:

(1) The written value can be read again later.
(2) For that to be possible it has to be monoid so that multiple (or
zero) values can be combined.

I fell say that this is a bit restricting. Sometimes, the written
value can be lost - either used to compute something else or for
example sent out using some IO action to a file, network etc. For
example, I'd like to create an IO-based writer monad whose `tell` logs
its argument somewhere - prints it, stores to a file etc.

So what I'm suggesting is to have another type class between Monad and
MonadWriter, let's say MonadTell, which only allows to write values,
not to retrieve them later:

> {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, FunctionalDependencies 
> #-}
> import Control.Monad
> import Control.Monad.Trans
> import qualified Control.Monad.Writer as W
> import qualified Control.Monad.Reader as R
> import Data.Monoid
>
> class Monad m => MonadTell w m where
> tell :: w -> m ()
> tell w = writer ((), w)
> writer :: (a, w) -> m a
> writer ~(a, w) = tell w >> return a

(We don't need fun.deps. here, they're needed in MonadWriter because
of `listen`. IDK if it'd be still better to add fun.dep. just to
eliminate typing problems?)

And MonadWriter would be defined by inheriting from MonadTell:

> class (MonadTell w m, Monoid w) => MonadWriter' w m | m -> w where
> listen :: m a -> m (a, w)
> pass :: m (a, w -> w) -> m a

Now we could use MonadWriter as before, but we could also make more
generic writers like:

> newtype Log = Log String deriving Show
> -- Prints logs to stdout.
> instance MonadTell Log IO where
> tell (Log s) = putStrLn s
>
> -- Collects the length of written logs.
> instance Monad m => MonadTell Log (W.WriterT (Sum Int) m) where
> tell (Log s) = W.tell (Sum $ length s)
>
>
> main = do
> let l = Log "Hello world"
> tell l
> print . getSum . W.execWriter $ (tell l :: W.Writer (Sum Int) ())

The same applies to MonadReader. We could make another type class
between Monad and MonadReader just with `ask`:

> class Monad m => MonadAsk r m | m -> r where
> ask :: m r

This would allow us to write instances like

> instance MonadAsk Log IO where
> ask = liftM Log getLine

Does it make sense?

Best regards,
Petr Pudlak

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


Re: [Haskell-cafe] forkProcess, forkIO, and multithreaded runtime

2012-10-17 Thread Alexander Kjeldaas
On 17 October 2012 00:17, Mike Meyer  wrote:

> On Tue, 16 Oct 2012 21:55:44 +0200
> Alexander Kjeldaas  wrote:
>
> > There are variants of this, but the meta-problem is that at the point in
> > time when you call forkProcess, you must control all threads, ensuring
> that
> > *all invariants hold*.  Thus no locks held, no thread is in the C
> library,
> > no foreign calls active etc.  As an example, if one thread is in the C
> > library doing some stdio, then the invariants in that library will not
> > hold, and you cannot expect stdio to work in the child.  This means that
> > the only thing you can really do in the child process is call exec.
>
> Further, you can only call exec if you make sure that the exec
> correctly reverts everything back to a state where those invariants
> hold. Mostly, this is automatic as resources get freed on exec and "do
> the right thing." Locks on file descriptors that aren't closed on exec
> will leave dangling locks, and locks on files that are closed on exec
> will unexpectedly close them in the parent.
>
>
Right.  It should be renamed mostlyUnsafeForkProcess, assuming the
multi-threaded RTS is "mostly" the default one.

Alexander


> --
> Mike Meyer   http://www.mired.org/
> Independent Software developer/SCM consultant, email for more information.
>
> O< ascii ribbon campaign - stop html mail - www.asciiribbon.org
>
> ___
> 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] License of CloudHaskell code write by Haskell language.

2012-10-17 Thread Edsko de Vries
Hi Chatsiri,

Yes, there are multiple backends for Cloud Haskell. The Azure backend
is, as you say, work in progress, although it's almost in a usable
state and we hope to release a first version (with minimal
functionality) soon. There is also the SimpleLocalnet backend which
you can use for local networks and is very convenient during
development.

Provided that you can use the TCP transport, the development of other
backends should not be too difficult. For instance, it should be
relatively little work to develop a backend for Amazon's EC2
infrastructure (especially now that there is a much improved version
of the Haskell bindings for libssh2).

If however you need to develop a backend which requires a different
network transport (such as UDP, say), you would need to develop a new
Network.Transport implementation, which is a more serious undertaking.

Edsko

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


Re: [Haskell-cafe] Solving integer equations in Haskell

2012-10-17 Thread Justin Paston-Cooper
Thanks for all the informative replies. SBV seems the simplest solution
right now, and speed isn't too much of an issue here. Anything under 20
seconds per solution should be bearable.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] poor performance when generating random text

2012-10-17 Thread Alfredo Di Napoli
What about this? I've tested on my pc and seems pretty fast. The trick is
to generate the gen only once. Not sure if the inlines helps, though:

import qualified Data.Text as T
import System.Random.MWC
import Control.Monad
import System.IO
import Data.ByteString as B
import Data.Word (Word8)
import Data.ByteString.Char8 as CB


{- | Converts a Char to a Word8. Took from MissingH -}
c2w8 :: Char -> Word8
c2w8 = fromIntegral . fromEnum


charRangeStart :: Word8
charRangeStart = c2w8 'a'
{-# INLINE charRangeStart #-}

charRangeEnd :: Word8
charRangeEnd = c2w8 'z'
{-# INLINE charRangeEnd #-}

--genString :: Gen RealWorld -> IO B.ByteString
genString g = do
randomLen <- uniformR (50 :: Int, 450 :: Int) g
str <- replicateM randomLen $ uniformR (charRangeStart, charRangeEnd) g
return $ B.pack str


writeCorpus :: FilePath -> IO [()]
writeCorpus file = withFile file WriteMode $ \h -> do
  let size = 10
  _ <- withSystemRandom $ \gen ->
  replicateM size $ do
text <- genString gen :: IO B.ByteString
CB.hPutStrLn h text
  return [()]

main :: IO [()]
main =  writeCorpus "test.txt"



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


Re: [Haskell-cafe] Is there a tool to see reduction steps?

2012-10-17 Thread Thomas Horstmeyer
There is Hood [11 and its graphical front-end GHood [2]. I have never 
used them myself however, only seen them demonstrated. Normally, using 
Debug.Trace is enough for me.



[1] http://www.ittc.ku.edu/csdl/fpg/Tools/Hood
[2] http://community.haskell.org/~claus/GHood/


Thomas


Am 10.10.2012 22:53, schrieb Daryoush Mehrtash:

I have been given a piece of code that uses Tie-ing the Knot concept to
label a tree of nodes in breath first manner.  It seems to work fine,
but  I am having trouble expanding the code on my own to see the
evaluation  process.   I like to know if there is a tools to use to see
the reduction steps.




data Tree = Leaf | Node Tree Int Tree deriving Show

label (Node ln _ rn) ((h:r):rest) = (Node lr h rr, r:r2) where
 (lr, r1) = label ln rest
 (rr, r2) = label rn r1
label _ _  = (Leaf, [])
lt t = let (r, unused) = label t ([1..]:unused)
in r





--
Daryoush

Weblog: http://onfp.blogspot.com/


___
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] poor performance when generating random text

2012-10-17 Thread Gregory Collins
System.Random is very slow. Try the mwc-random package from Hackage.

On Wed, Oct 17, 2012 at 9:07 AM, Dmitry Vyal  wrote:

> Hello anyone
>
> I've written a snippet which generates a file full of random strings. When
> compiled with -O2 on ghc-7.6, the generation speed is about 2Mb per second
> which is on par with interpreted php. That's the fact I find rather
> disappointing. Maybe I've missed something trivial? Any suggestions and
> explanations are welcome. :)
>
> % cat ext_sort.hs
> import qualified Data.Text as T
> import System.Random
> import Control.Exception
> import Control.Monad
>
> import System.IO
> import qualified Data.Text.IO as TI
>
> gen_string g = let (len, g') = randomR (50, 450) g
>in T.unfoldrN len rand_text (len, g')
>  where rand_text (0,_) = Nothing
>rand_text (k,g) = let (c, g') = randomR ('a','z') g
>  in Just (c, ((k-1), g'))
>
> write_corpus file = bracket (openFile file WriteMode) hClose $ \h -> do
>   let size = 10
>   sequence $ replicate size $ do
> g <- newStdGen
> let text = gen_string g
> TI.hPutStrLn h text
>
> main = do
>   putStrLn "generating text corpus"
>   write_corpus "test.txt"
>
>
>
> % cat ext_sort.prof
> Wed Oct 17 10:59 2012 Time and Allocation Profiling Report (Final)
>
>ext_sort +RTS -p -RTS
>
> total time  =   32.56 secs   (32558 ticks @ 1000 us, 1
> processor)
> total alloc = 12,742,917,332 bytes  (excludes profiling overheads)
>
> COST CENTREMODULE  %time %alloc
>
> gen_string.rand_text.(...) Main 70.7   69.8
> gen_string Main 17.6   15.8
> gen_string.rand_text   Main  5.4   13.3
> write_corpus.\ Main  4.30.8
>
>
> individual inherited
> COST CENTRE   MODULE no. entries  %time %alloc
> %time %alloc
>
> MAIN MAIN67   00.00.0
> 100.0  100.0
>  main Main 135   00.00.0
> 100.0  100.0
>   write_corpusMain 137   00.00.0
> 100.0  100.0
>write_corpus.\ Main 138   14.30.8
> 100.0  100.0
> write_corpus.\.text   Main 140  100.00.0
>  95.7   99.2
>  gen_string   Main 141  10   17.6   15.8
>  95.7   99.2
>   gen_string.g'   Main 147  100.00.0
> 0.00.0
>   gen_string.rand_textMain 144251097435.4   13.3
>  77.5   83.2
>gen_string.rand_text.g'Main 148249097430.60.0
> 0.60.0
>gen_string.rand_text.(...) Main 14625009743   70.7   69.8
>  70.7   69.8
>gen_string.rand_text.c Main 145250097430.80.0
> 0.80.0
>   gen_string.len  Main 143  100.00.0
> 0.00.0
>   gen_string.(...)Main 142  100.60.3
> 0.60.3
>
> __**_
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/**mailman/listinfo/haskell-cafe
>



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


[Haskell-cafe] Call for Papers: Only Two Months Left - STVR Special Issue on Tests and Proofs

2012-10-17 Thread Achim D. Brucker
Apologies for duplicates.

*
   Two months until the deadline for  ***
   submitting a paper to the  ***
  STVR special issue on Tests and Proofs  ***
*


  CALL FOR PAPERS 
  STVR Special Issue on Tests and Proofs
http://lifc.univ-fcomte.fr/tap2012/stvr/

The Software Testing, Verification & Reliability (STVR) journal
(http://www3.interscience.wiley.com/journal/13635/home) invites 
authors to submit papers to a Special Issue on Tests and Proofs.

Background
==
The increasing use of software and the growing system complexity make
focused software testing a challenging task. Recent years have seen an
increasing industrial and academic interest in the use of static and
dynamic analysis techniques together. Success has been reported
combining different test techniques such as model-based testing,
structural testing, or concolic testing with static techniques such as
program slicing, dependencies analysis, model-checking, abstract
interpretation, predicate abstraction, or verification. This special
issue serves as a platform for researchers and practitioners to
present theory, results, experience and advances in Tests and Proofs
(TAP).

Topics
==
This special issue focuses on all topics relevant to TAP. In
particular, the topics of interest include, but are not limited to:
* Program proving with the aid of testing techniques
* New challenges in automated reasoning emerging from
  specificities of test generation
* Verification and testing techniques combining proofs and tests
* Generation of test data, oracles, or preambles by deductive
  techniques such as: theorem proving, model checking, symbolic
  execution, constraint logic programming, SAT and SMT solving
* Model-based testing and verification
* Automatic bug finding
* Debugging of programs combining static and dynamic analysis
* Transfer of concepts from testing to proving (e.g., coverage
  criteria) and from proving to testing
* Formal frameworks for test and proof
* Tool descriptions, experience reports and evaluation of test and
  proof
* Case studies combining tests and proofs
* Applying combination of test and proof techniques to new
  application domains such as validating security procotols or
  vulnerability detection of programs
* The processes, techniques, and tools that support test and proof

Submission Information
==
The deadline for submissions is 17th December, 2012. Notification of
decisions will be given by April 15th, 2013.

All submissions must contain original unpublished work not being
considered for publication elsewhere. Original extensions to
conference papers - identifing clearly additional contributions - are
also encouraged unless prohibited by copyright. Submissions will be
refereed according to standard procedures for Software Testing,
Verification and Reliability.  Please submit your paper electronically
using the Software Testing, Verification & Reliability manuscript
submission site. Select "Special Issue Paper" and enter "Tests and
Proofs" as title.

Important Dates:

* Paper submission: December 17, 2012
* Notification: April 15, 2013

Guest Editors
=
* Achim D. Brucker, SAP AG, SAP Research, Germany
  http://www.brucker.ch/
* Wolfgang Grieskamp, Google, U.S.A.
  http://www.linkedin.com/in/wgrieskamp
* Jacques Julliand, University of Franche-Comté, France
  http://lifc.univ-fcomte.fr/page_personnelle/accueil/8   

-- 
  Dr. Achim D. Brucker, SAP AG, SAP Research 
 Vincenz-Priessnitz-Str. 1, D-76131 Karlsruhe, Phone: +49 6227 7-52595
 http://www.brucker.ch

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


[Haskell-cafe] poor performance when generating random text

2012-10-17 Thread Dmitry Vyal

Hello anyone

I've written a snippet which generates a file full of random strings. 
When compiled with -O2 on ghc-7.6, the generation speed is about 2Mb per 
second which is on par with interpreted php. That's the fact I find 
rather disappointing. Maybe I've missed something trivial? Any 
suggestions and explanations are welcome. :)


% cat ext_sort.hs
import qualified Data.Text as T
import System.Random
import Control.Exception
import Control.Monad

import System.IO
import qualified Data.Text.IO as TI

gen_string g = let (len, g') = randomR (50, 450) g
   in T.unfoldrN len rand_text (len, g')
 where rand_text (0,_) = Nothing
   rand_text (k,g) = let (c, g') = randomR ('a','z') g
 in Just (c, ((k-1), g'))

write_corpus file = bracket (openFile file WriteMode) hClose $ \h -> do
  let size = 10
  sequence $ replicate size $ do
g <- newStdGen
let text = gen_string g
TI.hPutStrLn h text

main = do
  putStrLn "generating text corpus"
  write_corpus "test.txt"



% cat ext_sort.prof
Wed Oct 17 10:59 2012 Time and Allocation Profiling Report (Final)

   ext_sort +RTS -p -RTS

total time  =   32.56 secs   (32558 ticks @ 1000 us, 1 
processor)

total alloc = 12,742,917,332 bytes  (excludes profiling overheads)

COST CENTREMODULE  %time %alloc

gen_string.rand_text.(...) Main 70.7   69.8
gen_string Main 17.6   15.8
gen_string.rand_text   Main  5.4   13.3
write_corpus.\ Main  4.30.8


individual inherited
COST CENTRE   MODULE no. entries  %time %alloc   
%time %alloc


MAIN MAIN67   00.00.0 
100.0  100.0
 main Main 135   00.00.0   
100.0  100.0
  write_corpusMain 137   00.00.0   
100.0  100.0
   write_corpus.\ Main 138   14.30.8   
100.0  100.0
write_corpus.\.text   Main 140  100.00.0
95.7   99.2
 gen_string   Main 141  10   17.6   15.8
95.7   99.2
  gen_string.g'   Main 147  100.0
0.0 0.00.0
  gen_string.rand_textMain 144251097435.4   13.3
77.5   83.2
   gen_string.rand_text.g'Main 148249097430.6
0.0 0.60.0
   gen_string.rand_text.(...) Main 14625009743   70.7   69.8
70.7   69.8
   gen_string.rand_text.c Main 145250097430.8
0.0 0.80.0
  gen_string.len  Main 143  100.0
0.0 0.00.0
  gen_string.(...)Main 142  100.6
0.3 0.60.3


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