Re: [Haskell-cafe] I Need a Better Functional Language!

2012-04-10 Thread Grigory Sarnitskiy
 10.04.2012, 02:00, Ryan Ingram ryani.s...@gmail.com:
 A concurring opinion here, and an example.

 iff :: Bol - a - a - a
 iff True x _ = x
 iff False _ x = x

 f, g :: Bool - Bool
 f x = x
 g x = iff x True False

 Are these two functions equal?  I would say yes, they are.  Yet once you can 
 pattern match on functions, you can easily tell these functions apart, and 
 create a function

 h :: (Bool - Bool) - Bool
 such that h f = True but h g = False.

   -- ryan

I've just remembered an interesting statement that there is a language where 
each equivalence class of programs Dan Doel mentioned (f = g  iff  forall x. f 
x = g x) has a single program in it. That is there is a one-to-one 
correspondence between programs and functions. Though as far as I understood 
one cannot construct a translator from this language to another language.

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


[Haskell-cafe] I Need a Better Functional Language!

2012-04-05 Thread Grigory Sarnitskiy
Hello! I've just realized that Haskell is no good for working with functions!

First, what are 'functions' we are interested at? It can't be the usual 
set-theoretic definition, since it is not constructive. The constructive 
definition should imply functions that can be constructed, computed. Thus these 
are computable functions that should be of our concern. But computable 
functions in essence are just a synonym for programs.

One could expect from a language that bears 'functional' as its characteristic 
to be able to do everything imaginable with functions. However, the only thing 
Haskell can do with functions is to apply them to arguments and to feed them as 
arguments, run in parallel (run and concatenate programs).

Obviously, that's not all of the imaginable possibilities. One also can rewrite 
programs. And write programs that rewrite programs. And write programs that 
rewrite programs that rewrite the first programs and so on. But there is no 
such possibility in Haskell, except for introducing a DSL.

So now I wonder, what are the languages that are functional in the sense above? 
With a reasonable syntax and semantics, thus no assembler. I guess Lisp might 
be of this kind, but I'm not sure. In addition, I'm not a fan of parentheses. 
What else? Pure? Mathematica? Maxima?

Note, that the reflectivity is important.

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


[Haskell-cafe] How do you describe systems in general with Haskell?

2011-11-05 Thread Grigory Sarnitskiy
If you are to describe a system, which consists of several subsystems, how do 
you approach the problem? What types, classes, functions whatever do you 
introduce?

I guess it is a common problem, is there a general method? Just to describe, 
not to solve (though if the description implies the solution then it is 
wonderful).

Obviously this is not just a haskell-specific problem, but I think there might 
be people who are aware of the best current solution (category theory?).

For a dummy example, how would you describe the system from a fox, goose and 
bag of beans puzzle (wolf, goat and cabbage)?

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


[Haskell-cafe] Can't resolve class dependences (making Boolean class)

2011-09-13 Thread Grigory Sarnitskiy
Hello! I'm trying to have a class for booleans called Boolean (the methods are 
not complete):

class MyEq a where
(===) :: (Boolean b) = a - a - b

class (MyEq a) = Boolean a where
(/\) :: a - a - a

instance MyEq Bool where
x === y = x==y

instance Boolean Bool where
(/\) = ()

However, to make Bool an instance of Boolean I need to make it an instance of 
MyEq first, which I can't, because to define === I need Bool to be in Boolean. 
Indeed the code above give the error:

Could not deduce (b ~ Bool)
from the context (Boolean b)
  bound by the type signature for
 === :: Boolean b = Bool - Bool - b
  at 1.hs:8:5-18
  `b' is a rigid type variable bound by
  the type signature for === :: Boolean b = Bool - Bool - b
  at 1.hs:8:5
In the expression: x == y
In an equation for `===': x === y = x == y
In the instance declaration for `MyEq Bool'
Failed, modules loaded: none.


How can I overcome the issue?

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


Re: [Haskell-cafe] Can't resolve class dependences (making Boolean class)

2011-09-13 Thread Grigory Sarnitskiy
Thank you all guys, fromBool did the trick.

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


[Haskell-cafe] Question about type families

2011-09-13 Thread Grigory Sarnitskiy
Is there a way to make the following code working?

{-# LANGUAGE TypeFamilies #-}

data family Foo a

data instance (Num a)= Foo a = A a deriving Show

data instance (Fractional a) = Foo a = B a deriving Show


I want to have different constructors for 'Foo a' depending on a class of 'a'. 
Note also, that in the example above I also meant constructor A to be available 
for (Fractional a) = Foo, since in that case 'a' has Num too. How can I 
achieve it, maybe not with TypeFamilies? Current error is

Conflicting family instance declarations:
  data instance Foo a -- Defined at 1.hs:7:33-35
  data instance Foo a -- Defined at 1.hs:5:33-35

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


[Haskell-cafe] TypeOperators and Unicode

2011-09-12 Thread Grigory Sarnitskiy
I want to have Unicode symbols for type operator:

{-# LANGUAGE TypeOperators #-}

data a ── b = Foo a b

But it doesn't work. Any suggestions?

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


Re: [Haskell-cafe] TypeOperators and Unicode

2011-09-12 Thread Grigory Sarnitskiy
Still

{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UnicodeSyntax #-}

data a ── b = Foo a b

leads to

test.hs:4:6: Malformed head of type or class declaration: a ── b
Failed, modules loaded: none.

12.09.2011, 11:56, Maciej Marcin Piechotka uzytkown...@gmail.com:
 On Mon, 2011-09-12 at 11:51 +0400, Grigory Sarnitskiy wrote:

  I want to have Unicode symbols for type operator:

  {-# LANGUAGE TypeOperators #-}

 Add also:

 {-# LANGUAGE UnicodeSyntax #-}

  data a ── b = Foo a b

  But it doesn't work. Any suggestions?

 Regards

 ___
 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] Can I have a typeclass for topological spaces?

2011-08-11 Thread Grigory Sarnitskiy
Hello! I just wonder whether it is possible to have a typeclass for topological 
spaces?

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


Re: [Haskell-cafe] Can I have a typeclass for topological spaces?

2011-08-11 Thread Grigory Sarnitskiy
Oh, I guess the class would look something like that:

class TopologicalSpace a where
ifOpen :: (Subset a) - Bool

and Subset x is a type corresponding to subsets of x.

11.08.2011, 17:52, Grigory Sarnitskiy sargrig...@ya.ru:
 Hello! I just wonder whether it is possible to have a typeclass for 
 topological spaces?

 ___
 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] Function returning the type of its argument.

2011-07-29 Thread Grigory Sarnitskiy
It is not possible in Haskell, moreover it seems to be too alien to Haskell. 
Nevertheless, is there an extension which would allow to write a function that 
returns the type of its argument?

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


[Haskell-cafe] GHC handles badly with math formulas

2011-06-13 Thread Grigory Sarnitskiy
I've noted several times that GHC doesn't evaluate formulas for Double values 
during compilation.

That is using
4.2326514735445615 instead of (512 / 0.844)**(1/3)
or
0.906179845938664 instead of (1/3) * sqrt(5 + 2 * sqrt(10 / 7))

This can lead to significant slowdown if such values are called often. It's not 
always convenient to use where or let to reduce the number of calculations of 
such constants so I wonder how to force GHC to evaluate them during compilation?

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


[Haskell-cafe] Looking for n-body example with repa.

2011-05-30 Thread Grigory Sarnitskiy
Hello!

I'm studying repa package and trying to implement O(N^2) n-body code. I'm using 
Array DIM2 Double to represent the collection of particles.

I've managed to write a function which calculates the energy of one particle in 
the field of others but I'm struggling to write a code to calculate the energy 
of the whole system.

Maybe someone here has already written such code?

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


[Haskell-cafe] Accelerate package (CUDA). How to actually create an array?

2011-05-16 Thread Grigory Sarnitskiy
Hello!

I'm probing CUDA with Haskell, accelerate package to be exact. Sound stupid, 
but I couldn't find how to actually construct an array, for example Vector 
Float.

There is quite a number of examples provided with the package, but they seem 
not simple enough for me just to start.

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


Re: [Haskell-cafe] Accelerate package (CUDA). How to actually create an array?

2011-05-16 Thread Grigory Sarnitskiy
 There's fromIArray and fromList [1].  Does that answer your question?

Huh, yes, thank you! But still I don't get it. Neither

arr1 = fromList 3 [1,2,3] :: Array DIM1 Int

nor

arr1 = fromList (1,3) [1,2,3] :: Array DIM1 Int

works

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


[Haskell-cafe] parMap doesn't work fine

2011-05-12 Thread Grigory Sarnitskiy
Hello!

I've just started using parallel computations in Haskell. parMap works fine, it 
is so easy to use. However, parMap fails with functions returning lazy 
structures, e.g. tuples.

This code works as expected:

(parMap rpar) bm tvalues

bm :: Double - Double is some heavy function. But if I want to return list of 
pairs (t, bm t) it doesn't use cpu cores fine (only one is in use):

(parMap rpar) (\t - (t, bm t)) tvalues

The same is valid for functions returning lists. How do I use multiple cores 
with functions returning tuples?

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


[Haskell-cafe] Exception for NaN

2011-05-12 Thread Grigory Sarnitskiy
How do I make my program stop whenever it gets somewhere NaN as a result during 
a calculation? If there is no appropriate flag for ghc maybe there exist flags 
for C to use in optc.

I don't want NaN to propagate, it is merely stupid, it should be terminated.

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


[Haskell-cafe] Painless parallelization.

2011-04-19 Thread Grigory Sarnitskiy
Hello, I'm searching a way to benefit from modern hardware in my programs.

I consider parallel programing to be actually easier than sequential one. 
Parallel computation allows to avoid sophisticated algorithms that were 
developed to gain performance on sequential architecture. It should also allow 
to stop bothering about using immutable objects --- immutable parallel arrays 
should be as fast as mutable ones, right? (provided there is enough cores)

So what are the options to write a pure functional parallel code with the level 
of abstraction I used in Haskell? So far I've found Data Parallel Haskell for 
multicore CPU's and Data.Array.Accelerate for GPU's. It would be nice to have 
something at the release state, rather than some beta.

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


[Haskell-cafe] Deciding equality of functions.

2011-04-09 Thread Grigory Sarnitskiy
I guess that deciding whether two functions are equal in most cases is 
algorithmically impossible. However maybe there exists quite a large domain of 
decidable cases? If so, how can I employ that in Haskell?

It is a common situation when one has two implementations of the same function, 
one being straightforward but slow, and the other being fast but complex. It 
would be nice to be able to check if these two versions are equal to catch bugs 
in the more complex implementation.

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


[Haskell-cafe] Data constructor synonyms

2011-03-18 Thread Grigory Sarnitskiy
Hello! Assume I have a type MyType with the constructor GeneralConstructor:

data MyType = GeneralConstructor [Double]

but I also want to have a separate name for special case of this constructor:

SpecialConstructor Double

so SpecialConstructor a = GeneralConstructor (a:[]) that is

SpecialConstructor 5 was exactly the same as GeneralConstructor [5].

And for example instead of writing GeneralConstructor [0] I would like to use 
constructor Zero. It's all just for convenience.

How can I achieve this? Well, of course I always can use sed to replace 
SpecialConstructor 5 with  GeneralConstructor [5] in program sources, but it's 
not convenient.

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


Re: [Haskell-cafe] Data constructor synonyms

2011-03-18 Thread Grigory Sarnitskiy
18.03.2011, 14:22, Roel van Dijk vandijk.r...@gmail.com;:

  Remember that constructors are functions, except that you can't
  pattern match against them.

..

  The downside is that you can't pattern-match against these functions.

The thing is that I need pattern matching, just functions won't do.

Anyway, a new question arose.  If I have already declared a type, can I add new 
constructors to it from other modules?

Maybe there are some GHC extensions to solve both these problems.

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


[Haskell-cafe] Effective function representation.

2011-01-22 Thread Grigory Sarnitskiy
Hello!

I need to deal with functions of type (Double - Double). I need Fourier 
transform, integration, + - * / operations, value of a function in a point, 
probably composition.

However it is not very effective to use straightforwardly this type. Since 
functions in question are rather smooth (if not analytical), the best option 
would be to use some kind of pointwise representation (e.g. lists, arrays). But 
in this case the code wouldn't be so easy to understand and implement, compact 
and so on.

Is there some libraries which allow me to work with functions as if their type 
was (Double - Double), but indeed it was something faster?

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


[Haskell-cafe] Equivalence of two expressions

2010-07-10 Thread Grigory Sarnitskiy
I'm not very familiar with algebra and I have a question.

Imagine we have ring K. We also have two expressions formed by elements from K 
and binary operations (+) (*) from K.

Can we decide weather these two expressions are equivalent? If there is such an 
algorithm, where can I find something in Haskell about it?

If there is no such algorithm for a ring, maybe there is for a field?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Friedberg numberings.

2010-02-18 Thread Grigory Sarnitskiy
Hello! The question is not about Haskell, but I don't know where else to ask.

In the book Computable functions by Vereshchagin and Shen it is said that it 
is possible to invent a programming language such that each programming problem 
has a unique solution in it. The author claims that this statement is a 
rewording of the theorem, that there is a universal computable function, such 
that any computable function has exactly one number.

I wonder has such language been actually constructed?

the book itself (look at the bottom of p 30 for the statement):

http://books.google.ru/books?id=A6uvsks0abgCpg=PA30#v=onepageq=f=false
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Program with ByteStrings leads to memory exhaust.

2009-09-14 Thread Grigory Sarnitskiy
I have a simple program that first generates a large (~ 500 mb) file of random 
numbers and then reads the numbers back to find their sum.
It uses Data.Binary and Data.ByteString.Lazy.

The problem is when the program tries to read the data back it quickly (really 
quickly) consumes all memory.

The source: http://moonpatio.com/fastcgi/hpaste.fcgi/view?id=3607#a3607

or:

module Main where

import Data.Binary
import Data.Int
import System.Random
import qualified Data.ByteString.Lazy as BL

encodeFileAp f = BL.appendFile f . encode
path = Results.data
n = 20*1024*1024 :: Int

getBlockSize :: BL.ByteString - Int64
getBlockSize bs = round $ (fromIntegral $ BL.length bs) / (fromIntegral n)

fillFile :: StdGen - Int - IO ()
fillFile _ 0 =return ()
fillFile gen i = do
let (x, gen') = random gen :: (Double, StdGen)
encodeFileAp path x
fillFile gen' (i-1)

processFile :: BL.ByteString - Int64 - Int - Double - Double
processFile bs blockSize 0 sum = sum
processFile bs blockSize i sum = let
tmpTuple = BL.splitAt blockSize bs
x = decode $ fst $! tmpTuple
in processFile (snd tmpTuple) blockSize (i-1) $! sum + x

main = do
fillFile (mkStdGen 42) n
results - BL.readFile path
putStrLn $ show $ processFile results (getBlockSize results) n 0
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Solved: [Was: Re: [Haskell-cafe] Program with ByteStrings leads to memory exhaust]

2009-09-14 Thread Grigory Sarnitskiy
 I have tweaked this program a few ways for you. 
 The big mistake (and why it runs out of space) is that you take
 ByteString.Lazy.length to compute the block size. This forces the entire
 file into memory -- so no benefits of lazy IO.
 As a separate matter, calling 'appendFile . encode' incrementally for
 each element will be very slow. Much faster to encode an entire list in
 one go.
 Finally, using System.Random.Mersenne is significantly faster at Double
 generation that System.Random.

Thank you! Just excellent! // I'm so happy :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] How to derive instance for type without exported constructor?

2009-09-04 Thread Grigory Sarnitskiy
In System.Random StdGen is defined as

data StdGen = StdGen Int32 Int32

but its constructor StdGen is not exported. How to make StdGen to be an 
instance of Binary? The following won't work:

instance Data.Binary.Binary StdGen where
put (StdGen aa ab) = do
Data.Binary.put aa
Data.Binary.put ab
get = do
aa - get
ab - get
return (StdGen aa ab)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to derive instance for type without exported constructor?

2009-09-04 Thread Grigory Sarnitskiy

 {-# OPTIONS_GHC -fglasgow-exts -XGenerics -package lang #-}

Got some problems:

Could not find module `Generics':
  it is a member of package ghc-6.8.2, which is hidden
Failed, modules loaded: none.

and for ghci test.hs -fglasgow-exts -XGenerics -package lang

ghc-6.8.2: unknown package: lang

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


Re: [Haskell-cafe] How to derive instance for type without exported constructor?

2009-09-04 Thread Grigory Sarnitskiy

 This time I've checked that it really compiles. Pretty much sure it works.

But how?! I'can't compile it:

test.hs:11:2:
Conflicting definitions for `put''
Bound at: test.hs:11:2-5
  test.hs:13:2-5
  test.hs:20:2-5
In the default-methods for class Binary'

test.hs:12:2:
Conflicting definitions for `get''
Bound at: test.hs:12:2-5
  test.hs:15:2-5
  test.hs:21:2-5
In the default-methods for class Binary'
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to derive instance for type without exported constructor?

2009-09-04 Thread Grigory Sarnitskiy
Well, I've managed to produce a solution, quite ugly and unefficient. Still it 
works (and I really need it). StdGen serialization occurs only once during 
computation that lasts several hours, so the speed is not vital for me. Here is 
my solution:

module Main where

import System.Random
import Data.Binary
import Data.Int

data StdGen' = StdGen' Int32 Int32 deriving (Show)

gen2gen' :: StdGen - StdGen'
gen2gen' gen = let
[g1, g2] = words $ show $ gen
g1' = read g1 :: Int32
g2' = read g2 :: Int32
in StdGen' g1' g2'

gen'2gen :: StdGen' - StdGen
gen'2gen (StdGen' g1' g2') = let
gen = read $ show g1' ++ ' ':(show g2') :: StdGen
in gen

instance Data.Binary.Binary StdGen' where
put (StdGen' aa ab) = do
Data.Binary.put aa
Data.Binary.put ab
get = do
aa - get
ab - get
return (StdGen' aa ab)

instance Data.Binary.Binary StdGen where
put gen = put $ gen2gen' gen
get = do
gen' - get
return (gen'2gen gen')
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Cabal install specific version of a package

2009-09-02 Thread Grigory Sarnitskiy
How to install specific version of a package (derive 0.1.4)?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Can't derive Binary for StdGen

2009-08-20 Thread Grigory Sarnitskiy
Hello! I'm trying to derive Binary for StdGen with DrIFT:

module Main where

import System.Random
import Data.Binary

{-!for StdGen derive : Binary !-}

data Foo = Foo StdGen StdGen deriving (Show) {-! derive : Binary !-}

but I got  error  DrIFT: can't find module System/Random
What shall I do?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Got problems with classes

2009-08-17 Thread Grigory Sarnitskiy
Hello! I can't understand why the following dummy example doesn't work.

{-# OPTIONS -XTypeSynonymInstances #-}
{-# OPTIONS -XFlexibleInstances #-} 
module Main where
import Data.Array.Unboxed

class Particle p

type ParticleC  =  (Double, Double, Double)
instance Particle ParticleC

class Configuration c where
getParticleI :: (Particle p) = c - Int - p

type Collection p = UArray (Int,Int) Double
instance Configuration (Collection p) where
getParticleI config i = (1,1,1) :: ParticleC
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Got problems with classes

2009-08-17 Thread Grigory Sarnitskiy
Thank you all, and especially Bulat. I've folowed the links and solved the problem in a new way.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Program with profiling runs faster than without

2009-07-14 Thread Grigory Sarnitskiy
14.07.09, 12:37, Grigory Sarnitskiy sargrig...@ya.ru:

 Hello! I can't understand why the following happens.
 ghc --make -fforce-recomp -O2 -fexcess-precision -fvia-C -optc-O2 Run.lhs -o 
 Run -prof -auto-all
 and
 time ./Run TestSim
 seems to be much faster (I got ~4 times faster indeed) than just
 ghc --make -fforce-recomp -O2 -fexcess-precision -fvia-C -optc-O2 Run.lhs -o 
 Run
 and
 time ./Run TestSim
 with ghc 6.8.2 on pentium 4 2.4 GHz under Ubuntu
 I was on my way to optimize the program when I've discovered this. The 
 program is rather complicated and badly optimized but still I think it is 
 quite strange to the profiled version to run faster. All necessary files I 
 send with this letter (Tann.7z).

Well, I've tested the code with ghc 6.10.3 under Windows --- the result is 
quite the same, however with the native binary compilier (not via C) the redult 
is even more drastic. I'm really interested how to obtain the same speed 
withput profiling compilation.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Program with profiling runs faster than without

2009-07-14 Thread Grigory Sarnitskiy
14.07.09, 15:16, Malcolm Wallace malcolm.wall...@cs.york.ac.uk:

 This is only a guess, but maybe there is a context-qualified CAF-like  
 value that is being re-evaluated multiple times in the non-profiling  
 case, but is appropriately monomorphised in the profiling case, so it  
 is only evaluated once?
 Regards,
  Malcolm

And I guess you are quite right. I knew there is a poorly optimized place in my 
program, but I didn't  touch it for some ideological reasons. But this morning 
I get how to optimize it in an ideological friendly manner, so now without 
profiling the program ~ 2 times faster. The speed of profiled version hasn't 
changed, hence I've manually done some work the compiler does during profiling.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Array Binary IO molecular simulation

2009-05-03 Thread Grigory Sarnitskiy
To sum up here is the example that can write two arrays in one file and then 
read this two arrays back. To restore written data it just reads the file into 
bytestring, then splits the bytestring into equal parts. The parts are decoded. 
I suppose the method is suitable for decoding files with unboxed arrays of 
equal size.

import Data.Array.Unboxed
import Data.Binary
import qualified Data.ByteString.Lazy as BL
import IO

a = listArray ((1,1),(3,2)) [3,4,5,6,7,8] :: UArray (Int, Int) Float
b = listArray ((1,1),(3,2)) [9,10,11,12,13,14] :: UArray (Int, Int) Float

encodeFile2 f = BL.appendFile f . encode

encoder = do
encodeFile Results.txt a
encodeFile2 Results.txt b

decoder = do
contents - BL.readFile Results.txt
print $ (show (decode (fst (BL.splitAt 118 contents)) :: UArray (Int, Int) 
Float))
print $ (show (decode (snd (BL.splitAt 118 contents)) :: UArray (Int, Int) 
Float))
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Array Binary IO molecular simulation

2009-05-03 Thread Grigory Sarnitskiy
To sum up here is the example
that can write two arrays in one file and then read this two arrays
back. To restore written data it just reads the file into bytestring,
then splits the bytestring into equal parts. The parts are decoded. I
suppose the method is suitable for decoding files with unboxed arrays
of equal size.

import Data.Array.Unboxed
import Data.Binary
import qualified Data.ByteString.Lazy as BL
import IO

a = listArray ((1,1),(3,2)) [3,4,5,6,7,8] :: UArray (Int, Int) Float
b = listArray ((1,1),(3,2)) [9,10,11,12,13,14] :: UArray (Int, Int) Float

encodeFile2 f = BL.appendFile f . encode

encoder = do
    encodeFile "Results.txt" a
    encodeFile2 "Results.txt" b

decoder = do
    contents - BL.readFile "Results.txt"
    print $ (show (decode (fst (BL.splitAt 118 contents)) :: UArray (Int, Int) Float))
    print $ (show (decode (snd (BL.splitAt 118 contents)) :: UArray (Int, Int) Float))
P.S. I've already sent this letter to mailist several ours ago, but it wasn't published :-/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Array Binary IO molecular simulation

2009-05-02 Thread Grigory Sarnitskiy
 2009/05/02 Jason Dusek :The original poster should try serializing a tuple of arrays instead of serializing each array individually.Maybe, but I have some doubts.  I have to operate with thousands of arrays --- are tuples good in such case? Moreover it is desirable to write data as it is calculated to be sure it wont be lost if the program suddenly stops for some reason. Can tuple/array/list of arrays be serialized and written to the file without its whole computation, but just as new elements appear?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Array Binary IO molecular simulation

2009-05-01 Thread Grigory Sarnitskiy
Hello!I'm interested in computer simulation of molecular systems, especially liquids. Maybe some would say Haskell is far from best choice in the case, but I really like the ease of writing programs in Haskell.So I wonder of existing projects of such type, both Molecular dynamics and Monte Carlo methods. I've got also some technical questions. Now I'm using 2D DiffUArray to represent particle positions during the simulation (when there are lots of array updates). Is this reasonably fast (I want to use pure external interface of DiffArray)?During the simulation each nth cycle the current position is stored for further processing. I haven't done this stage yet. To store the position I'm going to turn DiffUArray to UArray and write it in the file using tools of Data.Binary. Unfortunately I failed to produce the working code to write lots of 2D UArrays and then to read them. I know how to write several arrays in a file, but not how to read them back. Could someone please help me? Just to show how I've thought of storing several arrays in one file:import Data.Array.Unboxedimport Data.Binaryimport qualified Data.ByteString.Lazy as BLa = listArray ((1,1),(3,2)) [3,4,5,6,7,8] :: UArray (Int, Int) Floatb = listArray ((1,1),(3,2)) [9,10,11,12,13,14] :: UArray (Int, Int) FloatencodeFile2 f = BL.appendFile f . encoderun = do encodeFile "Results.txt" a     encodeFile2 "Results.txt" b___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe