[Haskell-cafe] Conditional lens

2013-10-10 Thread Artyom Kazak
Hello! I am working with TypeReps, and while writing some functions I have noticed that I could use lenses to simplify them; however, I have stumbled upon some difficulties. First I’ll try to clarify which functions I want to write: * a function for converting TypeRep of, say, `Maybe x` to

Re: [Haskell-cafe] Bytestring map/zipWith rationale

2013-09-12 Thread Artyom Kazak
On Thu, 12 Sep 2013 18:24:24 +0400, Tom Ellis tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote: On Thu, Sep 12, 2013 at 09:21:20AM -0400, Scott Lawrence wrote: Something's always bothered me about map and zipWith for ByteString. Why is it map :: (Word8 - Word8) - ByteString -

Re: [Haskell-cafe] Proposal: New syntax for Haskell

2013-09-10 Thread Artyom Kazak
On Wed, 11 Sep 2013 00:20:26 +0400, Thiago Negri evoh...@gmail.com wrote: I hope these jokes do not cause people to be afraid to post new ideas. Agreed. I would also like to clarify that my message was much more a joke on the incomprehensibility of legal acts than on the original proposal.

Re: [Haskell-cafe] Proposal: New syntax for Haskell

2013-09-10 Thread Artyom Kazak
This might do for businesses, but clearly not adequate if we want Haskell/Cucumber (ever) to be suitable for use in government. Here I’d like to suggest a more rigorous approach, which hopefully will be considered for implementation instead of the original proposal.

[Haskell-cafe] Impredicative types and Lens?

2013-09-08 Thread Artyom Kazak
Here’s a small example, which, when compiled, gives an error. Why? {-# LANGUAGE FlexibleInstances, ImpredicativeTypes, TemplateHaskell #-} import Control.Lens class Item a where name :: a - String instance Item (String, Int) where name = fst

Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-04 Thread Artyom Kazak
Oops. Ben Gamari bgamari.f...@gmail.com писал(а) в своём письме Tue, 04 Jun 2013 04:41:53 +0300: To be perfectly clear, ByteString and Text target much different use-cases and are hardly interchangeable. While ByteString is, as the name suggests, a string of bytes, Text is a string of

Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-03 Thread Artyom Kazak
silvio silvio.fris...@gmail.com писал(а) в своём письме Mon, 03 Jun 2013 22:16:08 +0300: Hi everyone, Every time I want to use an array in Haskell, I find myself having to look up in the doc how they are used, which exactly are the modules I have to import ... and I am a bit tired of

Re: [Haskell-cafe] data types with overlapping component names (in one module)?

2013-04-16 Thread Artyom Kazak
I'll just leave it here: http://hackage.haskell.org/trac/ghc/wiki/Records ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] ifdef based on which OS you're on

2013-02-15 Thread Artyom Kazak
Andrew Cowie and...@operationaldynamics.com писал(а) в своём письме Fri, 15 Feb 2013 17:05:13 +0300: So my question is: what's an appropriate Haskell mechanism for building code that is OS / arch / distro specific? It's not like I have autoconf running generating me a config.h I could

Re: [Haskell-cafe] How far compilers are allowed to go with optimizations?

2013-02-06 Thread Artyom Kazak
Ouch, forgot the Cafe. Would you object to this particular optimisation (replacing an algorithm with an entirely different one) if you were guaranteed that the space behaviour would not change? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] list comprehansion performance has hug different

2013-01-29 Thread Artyom Kazak
Junior White efi...@gmail.com писал(а) в своём письме Tue, 29 Jan 2013 12:25:49 +0300: The only different in the two program is in the first is q - [1..n], qs - queens' (k-1), and the second is qs - queens' (k-1), q - [1..n]. In the first case `queens' (k-1)` is being recomputed for every q

Re: [Haskell-cafe] list comprehansion performance has hug different

2013-01-29 Thread Artyom Kazak
Junior White efi...@gmail.com писал(а) в своём письме Tue, 29 Jan 2013 12:40:08 +0300: Hi Artyom, Thanks! But I don't understand why in the first case queens' (k-1) is being recomputed n times? Because your list comprehension is just a syntactic sugar for concatMap (\q -

Re: [Haskell-cafe] list comprehansion performance has hug different

2013-01-29 Thread Artyom Kazak
Junior White efi...@gmail.com писал(а) в своём письме Tue, 29 Jan 2013 12:59:31 +0300: So this is a problem in lazy evaluation language, it will not appear in python or erlang, am i right? Not quite. Compilers of imperative languages don’t perform CSE (common subexpression elimination)

Re: [Haskell-cafe] quotRem and divMod

2013-01-29 Thread Artyom Kazak
Shachaf Ben-Kiki shac...@gmail.com писал(а) в своём письме Tue, 29 Jan 2013 09:09:37 +0300: That code is from base 4.5. Here's base 4.6: quotRem x@(I32# x#) y@(I32# y#) | y == 0 = divZeroError -- Note [Order of tests] | y == (-1) x ==

[Haskell-cafe] quotRem and divMod

2013-01-28 Thread Artyom Kazak
Hi! I’ve always thought that `quotRem` is faster than `quot` + `rem`, since both `quot` and `rem` are just wrappers that compute both the quotient and the remainder and then just throw one out. However, today I looked into the implementation of `quotRem` for `Int32` and found out that it’s

Re: [Haskell-cafe] Cannot read a large integer on linux

2013-01-14 Thread Artyom Kazak
Right, it was fixed in GHC 7.4.2. hackage.haskell.org/trac/ghc/ticket/5688 The trouble with old behaviour was that it had been creating a security breach (anybody could pass 1e1000 where an Integer was expected and cause a segmentation fault). 15.01.2013 2:41 пользователь Arnaud Bailly

Re: [Haskell-cafe] Gloss and relatively expensive computations

2012-12-27 Thread Artyom Kazak
You could create a new thread which would be 'forever' executing your extensive computation and updating some IOVar accordingly. The drawing function would do nothing except reading that IOVar and displaying its contents. Since drawing is cheap, this can be done at any reasonable rate. 28.12.2012

Re: [Haskell-cafe] edge: compile testing

2012-12-15 Thread Artyom Kazak
Compiled just fine on my machine. Ubuntu 12.10, Haskell Platform 2012.2.0.0, GHC 7.4.2, cabal-install 1.16.0.1. Christopher Howard christopher.how...@frigidcode.com писал(а) в своём письме Sat, 15 Dec 2012 06:52:22 +0300: Hey guys, to teach myself Haskell I wrote a little arcade game

[Haskell-cafe] isLetter vs. isAlpha

2012-11-21 Thread Artyom Kazak
Hello! I saw a question on StackOverflow about the difference between isAlpha and isLetter today. One of the answers stated that the two functions are interchangeable, even though they are implemented differently. I decided to find out whether the difference in implementation influences

Re: [Haskell-cafe] List all multiply/add combinations

2012-11-18 Thread Artyom Kazak
Jonas Almström Duregård jonas.dureg...@chalmers.se писал(а) в своём письме Mon, 19 Nov 2012 01:31:01 +0300: Hi, You can make a datatype that captures exactly the expressions you want (see code below). Essentially you want to make sure that a subtraction or addition never has another

Re: [Haskell-cafe] List all multiply/add combinations

2012-11-17 Thread Artyom Kazak
Instead of attacking the problem textually, try to create a datatype which would describe your expressions, then generate all values of this datatype, filter those you don’t need, and convert the rest into Strings. Currently your expressions are represented by “String” — conversion is very

Re: [Haskell-cafe] List all multiply/add combinations

2012-11-17 Thread Artyom Kazak
Sorry! I replied without reading your message properly. I could then work directly with parsing trees, and generate all binary trees of fixed lengths. But most of them would be unnecessary, so it seems like I'm attacking it from the wrong angle. They won’t be unnecessary if you generate them

Re: [Haskell-cafe] List all multiply/add combinations

2012-11-17 Thread Artyom Kazak
The following algorithm generates all possible expressions and throws away most of unnecessary duplicates. import qualified Data.Map as M data Expr = Num Int | Add Expr Expr | Sub Expr Expr | Mul Expr Expr | Div Expr Expr Rendering function is

Re: [Haskell-cafe] List all multiply/add combinations

2012-11-17 Thread Artyom Kazak
Indentation messed up… I have pasted the code here: http://hpaste.org/77864 ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Polyvariadic composition

2012-07-30 Thread Artyom Kazak
Hello, I have accidentally written my version of polyvariadic composition combinator, `mcomp`. It differs from Oleg’s version ( http://okmij.org/ftp/Haskell/polyvariadic.html#polyvar-comp ) in three aspects: a) it is simpler, b) it works without enumerating basic cases (all existing

Re: [Haskell-cafe] Detecting numeric overflows

2012-07-30 Thread Artyom Kazak
Евгений Пермяков permea...@gmail.com писал в своём письме Mon, 30 Jul 2012 09:47:48 +0300: Can someone tell me if there are any primitives, that used to detect machine type overflows, in ghc haskell ? I perfectly understand, that I can build something based on preconditioning of variables,

[Haskell-cafe] Importing modules in GHCi

2012-06-04 Thread Artyom Kazak
Hi Café, I would greatly appreciate your help. Entering the following in GHCi produces an error message… -- import Data.Time -- getCurrentTime = print interactive:1:20: No instance for (Show UTCTime) arising from a use of `print' Possible fix: add an

Re: [Haskell-cafe] Importing modules in GHCi

2012-06-04 Thread Artyom Kazak
Oh, I’m sorry. I have Haskell Platform 2011.2.0.1, not 2012.2.0.1. So I guess it was a bug in GHCi… ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Problem with packet documentation generated by cabal on windows 7

2012-05-25 Thread Artyom Kazak
I’m having the same problem on my Windows 7 laptop. The solution I’ve found is to use Internet Explorer — it isn’t perfect, but for some reason it is the only browser capable of handling these links. On Fri, May 25, 2012 at 01:19:11AM +0200, Nicu Ionita wrote: Hi cafe, I have a problem

Re: [Haskell-cafe] (+1) vs let inc=(+1)

2012-05-22 Thread Artyom Kazak
http://www.haskell.org/haskellwiki/Monomorphism_restriction ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] A functional programming solution for Mr and Mrs Hollingberry

2012-05-20 Thread Artyom Kazak
Challenge accepted! I have written a solution in Haskell; please merge :) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] A functional programming solution for Mr and Mrs Hollingberry

2012-05-20 Thread Artyom Kazak
Andreas Pauley apau...@gmail.com писал(а) в своём письме Sun, 20 May 2012 20:33:13 +0300: I want to see how elegant a solution I can get in a functional language, given that the problem description is not really elegant at all. It has a few annoying exceptions to the normal rules, typical of

Re: [Haskell-cafe] Unboxed Rationals?

2012-01-12 Thread Artyom Kazak
Yves Parès limestr...@gmail.com писал(а) в своём письме Thu, 12 Jan 2012 13:14:16 +0200: uvector is deprecated, its functionnalities has been ported into vector. Yes, but a Ratio a instance hasn't been ported. I admit that I have overlooked the “deprecated” warning, and agree that it is

Re: [Haskell-cafe] Unboxed Rationals?

2012-01-11 Thread Artyom Kazak
You can use Data.Vector.Unboxed. There isn't an instance for Ratio a, but it is easy to write one, since it would be very similar to Complex a. http://hackage.haskell.org/packages/archive/vector/0.9.1/doc/html/Data-Vector-Unboxed.html#t:Unbox ___

Re: [Haskell-cafe] Unboxed Rationals?

2012-01-11 Thread Artyom Kazak
Also, uvector already supports unboxed Ratios: http://hackage.haskell.org/package/uvector In fact, I am surprised that Data.Vector doesn't have a Ratio instance, but has a Complex instance. Any ideas, why? ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] On the purity of Haskell

2011-12-30 Thread Artyom Kazak
Gregg Reynolds d...@mobileink.com писал(а) в своём письме Fri, 30 Dec 2011 17:23:20 +0200: Regarding side-effects, they can be (informally) defined pretty simply: any non-computational effect caused by a computation is a side-effect. I wonder: can writing to memory be called a

Re: [Haskell-cafe] On the purity of Haskell

2011-12-30 Thread Artyom Kazak
Donn Cave d...@avvanta.com писал(а) в своём письме Fri, 30 Dec 2011 20:36:46 +0200: That's why we use terms in a sense that apply meaningfully to computer programming languages in general and Haskell in particular. To do otherwise - for example to insist on a definition of pure that could

Re: [Haskell-cafe] On the purity of Haskell

2011-12-30 Thread Artyom Kazak
Chris Smith cdsm...@gmail.com писал(а) в своём письме Fri, 30 Dec 2011 22:04:21 +0200: Computability is just a distraction here. The problem isn't whether getAnIntFromUser is computable... it is whether it's a function at all! Even uncomputable functions are first and foremost functions,

Re: [Haskell-cafe] On the purity of Haskell

2011-12-30 Thread Artyom Kazak
Chris Smith cdsm...@gmail.com писал(а) в своём письме Fri, 30 Dec 2011 22:28:36 +0200: I really think that the notion of “purity” appeared to convince C programmers. It would be silly to try to explain that “Int - IO Int” isn't really a function from Int to Int, monads, blah blah blah. So,

Re: [Haskell-cafe] I've just heard of a neat security measure that when you compile the code it generates different object code...

2011-12-17 Thread Artyom Kazak
I wonder, if there is any example of actual Haskell program cracked / reverse engineered? GHC-generated code is already quite hard to understand… ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] Strange GC timings

2011-11-12 Thread Artyom Kazak
Hello! The following program executes 1.5 seconds on my computer: ---CODE BEGIN- module Main where import Data.Array.IArray main = print (answers ! 100) nextAns :: (Int, Int, Float) - (Int, Int, Float) nextAns (a, n, r) = if

Re: [Haskell-cafe] Bounds checking pragma?

2011-11-10 Thread Artyom Kazak
2011/11/10 Daniel Fischer daniel.is.fisc...@googlemail.com: There's a problem here, unsafeAt uses an Int index into the array, while (!) uses the declared index type. Even skipping the bounds check, you'd still have to calculate the Int index for the replacement of (!). #ifdef

[Haskell-cafe] Bounds checking pragma?

2011-11-09 Thread Artyom Kazak
Hello! The (!) operator is short and nice. Unfortunately, when doing heavy computing, we have to use unsafeAt instead. It looks ugly and it is ugly, also. Some compilers for imperative languages like Free Pascal have an option to turn on/off bounds checking for arrays. Wouldn't it be

[Haskell-cafe] Additional functions of GMP

2011-08-11 Thread Artyom Kazak
GMP has a lot of functions, such as extracting roots, primality test, Legendre symbol, factorial and so on. These can be written in Haskell, of course, but isn't it better to use existing functions? They are also much faster than similar functions from NumericPrelude, I believe. I have

Re: [Haskell-cafe] Additional functions of GMP

2011-08-11 Thread Artyom Kazak
I'm writing a package (arithmoi) that will include reasonably fast implementations of those, but I never find the time to finish it :( Package is great, but sometimes it is useful to have such functions out of box (for example, when solving SPOJ problems). No, you can't, unfortunately (not

Re: [Haskell-cafe] Problem with GLUT - no visuals found

2011-06-23 Thread Artyom Kazak
It may be related to the problem which I encountered too: http://www.mail-archive.com/haskell-cafe@haskell.org/msg89460.html Try using GLUT from http://github.com/haskell-opengl/GLUT Hope that helps. --Artyom ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Artyom Kazak
Suppose iRecurse looks like this: iRecurse = do x - launchMissiles r - iRecurse return 1 As x is never needed, launchMissiles will never execute. It obviously is not what is needed. But in Haskell, standart file input|output is often lazy. It's a combination of buffering and

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Artyom Kazak
Scott Lawrence byt...@gmail.com писал(а) в своём письме Tue, 31 May 2011 23:29:49 +0300: On 05/31/2011 04:20 PM, Artyom Kazak wrote: Suppose iRecurse looks like this: iRecurse = do x - launchMissiles r - iRecurse return 1 As x is never needed, launchMissiles will never execute

Re: [Haskell-cafe] Reverse Show instance

2011-05-19 Thread Artyom Kazak
And I can declare an instance for (x, y) which does NOT implies (Show x): instance Show (x, y) where show _ = I'm tuple! Hooray! Andrew Coppin andrewcop...@btinternet.com писал(а) в своём письме Fri, 20 May 2011 00:08:27 +0300: Cannot deduce (Show x) from context (Show (x, y)).

Re: [Haskell-cafe] I cannot find the module Data.Numbers.Primes

2011-05-17 Thread Artyom Kazak
Yes, of course there is! You can find the index of all functions, types, typeclasses etc. here: http://lambda.haskell.org/hp-tmp/docs/2011.2.0.0/doc-index.html KC kc1...@gmail.com писал(а) в своём письме Tue, 17 May 2011 20:33:05 +0300: Is there a way to tell when a function is included

Re: [Haskell-cafe] generic putback

2011-05-15 Thread Artyom Kazak
I'm sorry, but I don't fully understand what do you want from putback. If putback'ed action does io and then returns x, it's trivial: putback x io = io return x If you want putback'ed action to return x on its first call and do io on second, third... calls, then you need to put

Re: [Haskell-cafe] warning - Euler problem spoiler enclosed

2011-05-04 Thread Artyom Kazak
Barbara Shirtcliff ba...@gmx.com писал(а) в своём письме Wed, 04 May 2011 16:41:07 +0300: Also, note that lexOrder s@[_] = [s] is nicer than lexOrder s | length s == 1 = [s]. I agree that that initial version was a little clumsy, but your suggestion doesn't really seem to work:

[Haskell-cafe] GLUT error while using Gloss

2011-05-02 Thread Artyom Kazak
Hi Cafe! When I'm running examles from Gloss graphics library, all examples except gloss-hello are crashing with the following error: GLUT: Warning in gloss-easy: GL error: gloss-easy: stderr: hPutChar: invalid argument (character is not in the code page). A window with produced picture is showed

Re: [Haskell-cafe] GLUT error while using Gloss

2011-05-02 Thread Artyom Kazak
It's good to hear. Thanks! 2011/5/2 Jason Dagit dag...@gmail.com:  This is fixed in the git repository for GLUT, but I didn't push the fix to hackage yet: https://github.com/haskell-opengl/GLUT/pull/1 Sorry for the inconvenience! Jason ___

Re: [Haskell-cafe] How to use roots package?

2011-03-20 Thread Artyom Kazak
Oh. I have taken a wrong approach to the problem. I have written Newton method with cutting precision if it's more than N digits, and it finds an answer practically in no time. But still, it's very good, thank you! ___ Haskell-Cafe mailing list

[Haskell-cafe] How to use roots package?

2011-03-18 Thread Artyom Kazak
Hi Café! roots (http://hackage.haskell.org/package/roots) is a package to solve equations like f(x)==0. In RootFinder class there is an 'defaultNSteps' value, which is used as maximal count of iterations functions like findRoot and traceRoot can make. By default it is 250, but sometimes

Re: [Haskell-cafe] How large is the Haskell community ?

2011-02-13 Thread Artyom Kazak
Aaron Gray aaronngray.li...@gmail.com писал(а) в своём письме Sat, 12 Feb 2011 22:18:33 +0200: I was wondering if anyone had an idea or estimate as to how large the Haskell community is ? Aaron I've been subscribed to this list since the very start of the 2010 year, and I counted 1168 ±

[Haskell-cafe] A State Monad Tutorial

2010-10-19 Thread Artyom Kazak
Some time ago I have read A State Monad Tutorial (http://strabismicgobbledygook.wordpress.com/2010/03/06/a-state-monad-tutorial/). While reading, I was fixing some minor mistakes (okay, a lot of mistakes). After all, I had an idea to create PDF with fixed version. So, here it is:

[Haskell-cafe] Parallel Pi

2010-03-17 Thread Artyom Kazak
Hello! I tried to implement the parallel Monte-Carlo method of computing Pi number, using two cores: --PROGRAM module Main where import Random import Data.Ratio import Data.List import System.IO import GHC.Conc main = do putStrLn pi 1 putStr n: hFlush stdout t - getLine piMonte (read

[Haskell-cafe] Performance of Knight's Tour

2010-03-01 Thread Artyom Kazak
Hi! I'm learning Haskell, and now I'm trying to make framework for solving searching problems, such as Knight's Tour. For small boards it answers instantly. For 7x8 board - 23 seconds. For 8x8 board - more than 30 minutes (it hasn't finished yet). Where is the root of the evil? --program module

Re: [Haskell-cafe] Performance of Knight's Tour

2010-03-01 Thread Artyom Kazak
2010/3/1 Daniel Fischer daniel.is.fisc...@web.de: In the algorithm. You investigate far too many dead ends. Since for larger boards, the number of dead ends increases fast, larger boards take much much longer. With one little change, I get ... For a reason I don't understand, if the second

Re: [Haskell-cafe] Performance of Knight's Tour

2010-03-01 Thread Artyom Kazak
2010/3/1 Daniel Fischer daniel.is.fisc...@web.de: Am Montag 01 März 2010 19:29:45 schrieb Artyom Kazak: 2010/3/1 Daniel Fischer daniel.is.fisc...@web.de: In the algorithm. You investigate far too many dead ends. Since for larger boards, the number of dead ends increases fast, larger boards

Re: [Haskell-cafe] GHC RTS question

2010-02-24 Thread Artyom Kazak
2010/2/24 Brandon S. Allbery KF8NH allb...@ece.cmu.edu: On Feb 22, 2010, at 03:36 , Roman Cheplyaka wrote: * Anthony Cowley acow...@seas.upenn.edu [2010-02-21 14:15:00-0500] #! /usr/bin/env bash ./prog --RTS $*  ./prog --RTS $@ Otherwise it will work wrong if arguments contain quoted

[Haskell-cafe] GHC RTS question

2010-02-21 Thread Artyom Kazak
Hello everybody! I want to write a little program, that will receive a string as command-line argument and write it in the file. But if this string contains '+RTS', GHC runtime won't pass the rest of the string to my program. What can I do to avoid this?

Re: [Haskell-cafe] GHC RTS question

2010-02-21 Thread Artyom Kazak
Enclose it in double quotes (perhaps single quotes would also work) No, I want my program to work the same way as UNIX echo does. Without any double quotes. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] GHC RTS question

2010-02-21 Thread Artyom Kazak
2010/2/21 Daniel Fischer daniel.is.fisc...@web.de: Am Sonntag 21 Februar 2010 18:20:43 schrieb Artyom Kazak: Enclose it in double quotes (perhaps single quotes would also work) No, I want my program to work the same way as UNIX echo does. Without any double quotes. Okay, what about

[Haskell-cafe] Mysterious factorial

2009-12-30 Thread Artyom Kazak
Why fact2 is quicker than fact?! fact2 :: Integer - Integer fact2 x = f x y where f n e | n 2 = 1 | e == 0 = n * (n - 1) | e 0 = (f n (e `div` 2)) * (f (n - (e * 2)) (e `div` 2)) y = 2 ^ (truncate (log (fromInteger x) / log 2)) fact :: Integer - Integer fact 1 = 1 fact n = n * fact (n - 1) I