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

[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.

[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

[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 (/\) = ()

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'.

[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
+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

[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

[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

[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

[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

[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.

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

[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

[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] 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

[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

[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

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

[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

[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

[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

[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.

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'

[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

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

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'

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

[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] 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

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

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

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

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

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

[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