[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 `[x]`
  (for all x). It requires checking if the TyCon is `Maybe` and
  replacing it with []-TyCon. If it wasn’t `Maybe`, I return Nothing.

* a similar function for replacing `Char`s and `Lazy.Text`s to just
  `Text`. Again, if the TypeRep-to-be-replaced doesn’t satisfy my
  conditions, I return Nothing.

These two functions (and some others, I suppose) can be written concisely
with the help of one combinator. I don’t know how to write it as
a composable Lens, so I’ll give it here as an ad-hoc Lens-modifying
function instead:

ifL :: (a - Bool) - Lens s t a b - Lens s (Maybe t) (Maybe a) b
ifL p l = lens getter setter
  where
get s = getConst $ l Const s
getter s   = let a = get s
 in  if p a then Just a else Nothing
setter s b = let a = get s
 in  if p a then Just (set l b s) else Nothing

It works like this:

 (0, 2)  ifL even fs .~ hello
Just (hello,2)

 (1, 2)  ifL even fs .~ hello
Nothing

With `ifL`, my initial ugly

changeTyCon :: TyCon - TyCon - TypeRep - Maybe TypeRep
changeTyCon tc tc' t | t^.tyCon == tc = Just $ t  tyCon .~ tc'
 | otherwise  = Nothing

boils down to

changeTyCon tc tc' = ifL (== tc) tyCon .~ tc'

Why did I call the initial version “ugly”? Well, because

a) it manually handles `Maybe`s, and
b) it has to perform both getting and setting (two passes).

So, my questions are:

1. What would be the idiomatic way to write `ifL`?

2. How can I do something like `t ^. ifL (== tc) tyCon`?
   Currently it doesn’t work because view’s type has been
   simplified in lens-3.9.

3. Perhaps it would be better to represent `ifL` as a Traversal
   which simply ignores values that don’t match the condition?
   Then I could (?) use `failover` to do what I want. I searched
   for something filter-like in lens library, but haven’t found
   anything.

4. If I haven’t missed anything and it indeed can’t be done with bare
   lens, would `ifL` or something similar be welcome as an addition
   to the library?

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


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 - ByteString

but

zipWith :: (Word8 - Word8 - a) - ByteString - ByteString - [a]


Well, what if you wanted to zipWith a function of type Word8 - Word8 -
Foo instead of Word8 - Word8 - Word8?


Then why doesn’t map take “Word8 - a”, but only “Word8 - Word8”?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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.

By the way, I am pretty impressed with this piece of Cucumber  
description/code:


  Scenario: Mislav creates a valid task with an upload
When I go to the Awesome Ruby Yahh task list page of the Ruby  
Rockstars project

When I follow + Add Task
And I fill in Task title with Ohhh upload
And I follow Attachment
When I attach the file features/support/sample_files/dragon.jpg to  
upload_file

And I press Add Task
And I wait for 1 second
And I should see Ohhh upload as a task name

I was much more sceptical when I had only seen the example in Niklas’s  
message.

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


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.


MODULE Data.List

  1st proposal

To promote prosperity, creativity, entrepreneurship, and innovation by
providing convenient functions operating on lists, and for other purposes.

   IN THE STANDARD LIBRARY OF HASKELL

   September 10, 2013

Mr. KAZAK of Russia, Saint-Petersburg (for himself and Mr. GEHR, Mr.  
HAMBÜCHEN,
Mr. WIEGLEY, Mr. ZIMMERMAN, Mr. CHEPLYAKA, Mr. ROSS, Mr. SNOYMAN, Mr.  
NEGRI,

Mr. YANG and Mr. FUJIMURA) introduced the following module; which was
referred to the Café of Haskell.


A MODULE

Be it approved by the General Public and Maintainers of `base` package,


SECTION ONE. SHORT TITLE; TABLE OF CONTENTS
===

(a) Short Title - This Module may be cited as the ‘Data.List module’.

(b) Table of Contents - The table of contents of this Module is as follows:

Sec. 1. Short title; table of contents.

...


TITLE I - HISTORY AND BACKGROUND


Sec. 101. Definitions.

Sec. 102. Action by Simon Peyton-Jones to protect Haskell users and
prevent success at all costs¹.

Sec. 103. Immunity for taking voluntary action against LANGUAGE pragmas
dedicated to theft of syntax.

Sec. 104. Immunity for taking voluntary action against libraries that
make heavy use of unsafePerformIO.

Sec. 105. Guidelines and study.

Sec. 106. Denying `base` maintainership to notorious Applicative = Monad
proposal supporters.


TITLE II — THE ‘FOLDL’ FUNCTION
---

Sec. 201. Type of ‘foldl’.

Sec. 202. Specification of ‘foldl’.

Sec. 203. Implementation of ‘foldl’.


END OF TABLE OF CONTENTS



 TITLE I — HISTORY AND DEFINITIONS

  SEC. 101. DEFINITIONS.

In this title:

(1) FUNCTION - The term ‘function’ has the meaning implied in the
Haskell 98 Report, even though it isn’t actually given there.

(2) LIST - The term ‘list’ means a datatype used to provide the means
of accessing data stored in it sequentially, starting with the first
element and moving to the next element without delay, i.e. in O(1) time.

(3) EMPTY LIST — The term ‘empty list’ denotes a list which does not
contain any data, explicitly or implicitly, and which restricts any of
the attempts to obtain its first element through the well-defined
mechanism of exceptions and compile-time pattern match failures.

(3) NON-EMPTY LIST - The term ‘non-empty list’ means a list which is
not an empty list.
 ...


 TITLE II — THE ‘FOLDL’ FUNCTION

SEC. 201. TYPE OF ‘FOLDL’

For any types A and B, be they sum types, product types, a valid  
combination

of sum and/or product types; types defined in the Standard Library, defined
by users of Haskell or defined in one of the Imported Modules; resulting
from execution of Template Haskell; from execution of a generator written  
in
another programming language, not excluding Haskell; or written by  
human(s):


  (a) function ‘foldl’ requires an argument which itself must be a  
function:


(1) which requires an argument of type A and shall produce a function:

(2) which requires an argument of type B and shall produce
a value of type A.

  (b) and shall produce a function:

(1) which requires an argument of type A and shall produce a function:

(2) which requires an argument of type, which denotes the set of all
lists, empty or non-empty, together with bottom and further
abominations, which shall contain elements of type B, and shall
produce a value of type A.


 SEC. 202. SPECIFICATION OF ‘FOLDL’

Assuming the following:

  (a) the argument of ′foldl’ is denoted by ‘f’.

  (b) the argument of the produced function is denoted by ′acc’.

  (c) the argument of the function, produced by the produced function,
  is denoted by ‘l’.

Then it shall be held that:

  (a) ‘foldl’ must be using ‘f’ while processing the elements of ‘l’, and
  it may not use any other function, either supplied to it implicitly
  or explicitly, defined in Data.List module, other modules included
  into Standard Library, Hackage or any other collection of modules.

(1) Other functions may be defined for internal use by ‘foldl’, but
they shall not be used to replace ‘f’, as it is deemed highly  
unlikely

that any of such defined functions are adequate replacements of ‘f’
and do not attempt to invade any country through means of launching
missiles.

  (b) ‘foldl’ must process ‘l’ as follows:

(1) it 

[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

type ItemFilter = Item a = a - Bool

data ItemBox = ItemBox { _itemFilter :: ItemFilter }
makeLenses ''ItemBox

The error is

Couldn't match type `a0 - Bool'
  with `forall a. Item a = a - Bool'
Expected type: ItemFilter
  Actual type: a0 - Bool
In the expression: b_aaZE
In the first argument of `iso', namely
  `\ (ItemBox b_aaZE) - b_aaZE'
In the expression: iso (\ (ItemBox b_aaZE) - b_aaZE) ItemBox

I’m using GHC 7.6.2, if it’s important.

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


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 characters in a
Unicode encoding. When you are talking about unstructured binary data,
you should most certainly be using ByteString.


Why create a special case? Right now you should use ByteString, yes, but I
wish I could just use a generic array of Word8.

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


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 staring at type signatures  
for 10 minutes to figure out how these arrays work every time I use them  
(It's even worse when you have to write the signatures). I wonder how  
other people perceive this issue and what possible solutions could be.


Recently I’ve started to perceive this issue as “hooray, we have lenses  
now, a generic interface for all the different messy stuff we have”. But  
yes, the inability to have One Common API for All Data Structures is  
bothering me as well.


Why do we need so many different implementations of the same thing? In  
the ghc libraries alone we have a vector, array and bytestring package  
all of which do the same thing, as demonstrated for instance by the  
vector-bytestring package. To make matters worse, the haskell 2010  
standard has includes a watered down version of array.


Indeed. What we need is `text` for strings (and stop using `bytestring`)  
and reworked `vector` for arrays (with added code from `StorableVector` —  
basically a lazy ByteString-like chunked array).



# Index

I don't really see a reason for having an index of a type other than Int  
and that starts somewhere else than at 0.


It’s a bad idea. I, for one, don’t really see how writing `Vector (Vector  
(Vector Int))` can be considered even remotely satisfying by anyone. And  
if you’re considering 3D arrays “a corner case”, then I’m afraid I can’t  
agree with you.


Also, arrays which allow negative indexing can save a lot of headache and  
prevent mistakes which generally occur when a programmer is forced to  
constantly keep in mind that index 2000 is actually 0 and 0 is −2000.



# Storable vs Unboxed

Is there really a difference between Storable and Unboxed arrays and if  
so can't this be fixed in the complier rather than having to expose this  
problem to the programmer?


Storable seems to be mainly for marshalling, and most people who need it  
are (probably) library writers. I don’t know for sure, though, but it  
doesn’t appear to be a big issue.



# ST s vs IO

This is probably the hardest to resolve issue. The easiest solution is  
probably to just have a module for each of them as in the array package.

I find the PrimState a bit complicated and circuitous.

The ideal solution would be to have

   type IO a = ST RealWorld# a

in the next haskell standard.


Sure, except that IO is actually *not* ST+Realworld, and only happens to  
be implemented like that in GHC (not in JHC, for instance). It has been  
discussed before:  
http://haskell.1045720.n5.nabble.com/IO-ST-RealWorld-td3190075.html . (Not  
to mention people attempting to rewrite RealWorld# values and create havoc  
and fire missiles everywhere expecting them to disappear the very moment  
they smile knowingly and `put` the original RealWorld# back.)


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


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 #include, right?


You can know the OS and arch without even resorting to CPP; see  
System.Info  
(http://hackage.haskell.org/packages/archive/base/latest/doc/html/System-Info.html),  
which defines `os` and `arch`.


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


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
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 (that  
is, n times). Of course it would matter :)


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


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 -
  concatMap (\qs - if isSafe q qs then [q:qs] else [])
(queens' (k-1)))
  [1..n]

Here `queens' (k-1)` does not depend on `qs`, and therefore it *could* be  
floated out of the lambda:


let queens = queens' (k-1)
in
concatMap (\q -
  concatMap (\qs - if isSafe q qs then [q:qs] else [])
queens)
  [1..n]

But it is an unsafe optimisation. Suppose that the `queens` list is very  
big. If we apply this optimisation, it will be retained in memory during  
the whole evaluation, which may be not desirable. That’s why GHC leaves  
this to you.


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


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) either; `queens' (k-1)` could have some side  
effects, after all, and performing a side effect only once instead of n  
times is a definite bug.


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


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 == minBound = (overflowError, 0)
| otherwise  = case x# `quotRemInt#` y# of
   (# q, r #) -
   (I32# (narrow32Int# q),
I32# (narrow32Int# r))

So it looks like it was improved in GHC 7.6. In particular, by this
commit:  
http://www.haskell.org/pipermail/cvs-libraries/2012-February/014880.html


Shacha


Well, I’m glad to know that it has been fixed in the newer GHC (I’m still  
on 7.4). Thanks!


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


[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  
not true:


quotRem x@(I32# x#) y@(I32# y#)
| y == 0 = divZeroError
| x == minBound  y == (-1) = overflowError
| otherwise  = (I32# (narrow32Int# (x# `quotInt#`  
y#)),
I32# (narrow32Int# (x# `remInt#`  
y#)))


Why? The `DIV` instruction computes both, doesn’t it? And yet it’s being  
performed twice here. Couldn’t one of the experts clarify this bit?


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


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 arnaud.oq...@gmail.com
написал:

 Hello,
 I am encountering a strange issue while trying to read a string into an
 integer.

 On windows 7 64bit, I have:

  read 18780189038289e49 :: Integer
 =187801890382890

 On linux (64bit, libgmp.so.3.5.2) I have:

  read 18780189038289e49 :: Integer
 *** Exception: Prelude.read: no parse

 That's weird and I really have no clue what's going on. I use ghci 7.4.2
 on linux and 7.4.1 on windows.

 What am I doing wrong ?

 Arnaud

 ___
 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] 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 3:22 пользователь Daniel Díaz Casanueva dhelta.d...@gmail.com
написал:

 Hello cafe!

 I'm having some performance issues trying to use gloss to make animations
 where each model step is relatively time expensive. I'm using the
 IO.Simulate module because my step function needs to do an IO operation
 which takes around 1 second (it may vary).

 I will try to give some details.

 I have the step function:

 step :: Model - IO Model
 step m = do
  ...
  p - slowOperation
  ...
  return newModel

 The rest of the program is small and simple. The drawing function (Model
 - IO Picture -- it is pure though) is as quick as simple. However, the
 program get stuck after the first iteration.

 In the other hand, I am using the animateIO function which ask me for an
 Int value to set up the number of simulation steps to take for each second
 of real time. But I'm more interested in the animation waiting for the
 simulation step to end. Does it make sense?

 I would be really thankful with any pointer here.

 Thanks in advance,
 Daniel Díaz.

 ___
 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] 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 called
The Edge, built on gloss. It is in hackage under the package name
edge. Are there a few kind souls who would be willing to compile it on
their machines and let me know if there are any problems at the
compiling level? In the past, I've had issues with Haskell code
compiling fine on my development system but not on others (due to
dependency-related issues). I want to double check this before I try to
make any distro-specific packages.

I developed with GHC 7.4 and cabal-install 1.16.0.2 on a Gentoo system.
Requires OpenGL and OpenAL (for sound).

cabal update  cabal install edge


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


[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  
performance, and look what I found:



import Criterion.Main
import Data.Char
fTest name f list = bgroup name $ map (\(n,c) - bench n $ whnf f c) list
tests = [(latin, 'e'), (digit, '8'), (symbol, '…'), (greek, 'λ')]
main = defaultMain [fTest isAlpha isAlpha tests, 
fTest isLetter isLetter tests]


produces this table (times are in nanoseconds):

 latin digit symbol greek
 - - -- -
   isAlpha  | 156   212   368310
   isLetter | 349   344   383310

isAlpha is twice as fast on latin inputs! Does it mean that isAlpha should  
be preferred? Why isn’t isLetter defined in terms of isAlpha in Data.Char?


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


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 subtraction or addition as its left operand.



I would also like to advertise a bit and show how this type can be
enumerated automatically by Feat (
http://hackage.haskell.org/package/testing-feat).


After a quick look, Feat seems to be awesome. Thanks! I don’t yet know how  
I am going to use it, but I hope an opportunity will present itself soon :)


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


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 cheap, but filtering is “hard” (since it boils down to parsing).  
Binary trees would suit you better.


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


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 in a right way. I will  
think about it and reply with a detailed answer as soon as possible.


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


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 highly imperfect. Either write one yourself, or  
change the

definition of Expr to something like “Num Int | App Op [Expr]” — this way
rendering would become much easier.


render :: Expr - String
render (Num n) = show n
render (Add a b) = ( ++ render a ++ + ++ render b ++ ) render (Sub  
a b) = ( ++ render a ++ - ++ render b ++ ) render (Mul a b) = (  
++ render a ++ * ++ render b ++ ) render (Div a b) = ( ++ render a  
++ / ++ render b ++ )


Let’s assume that we have lN numbers.


nums = [1, 2, 3]
lN   = length nums


Our goal is to build table of all possible expressions, which can be build
using numbers from i-th to j-th, where i, j are in range from 0 to lN-1.

We have to fill the table in the following order: numbers themselves,
expressions consisting of two numbers, three, four, … N.


table :: M.Map (Int, Int) [Expr]
table = M.fromList  $ [((i, i), [Num n] ) | (i, n) - zip [0..lN-1]  
nums]

 ++ [((i, j), calc i j) | i - [0..lN-1], j - [i+1,i+2..lN-1]]




answer = table M.! (0, lN-1)


Our next goal is a function which fills this table:


calc :: Int - Int - [Expr]
calc i j = do
  --elements from i to k will form one branch, k+1 to j — another
  k - [i,i+1..j-1]
  le - table M.! (i, k)
  re - table M.! (k+1, j)


We don’t want to generate both
  (a+b)+c and a+(b+c), or (a+b)-c and a+(b-c), or
  (a-b)-c and a-(b+c), or (a-b)+c and a-(b-c),
so we’re eliminating the second variant in each pair. Multiplication and
division follow the same pattern.


  case re of
Add _ _   - [Mul le re, Div le re]
Sub _ _   - [Mul le re, Div le re]
Mul _ _   - [Add le re, Sub le re]
Div _ _   - [Add le re, Sub le re]
otherwise - [Add le re, Sub le re, Mul le re, Div le re]


Here are generated expressions:

1*(2+3)  1/(2+3)  1*(2-3)  1/(2-3)  1+(2*3)  1-(2*3)  1+(2/3)  1-(2/3)
(1+2)+3  (1+2)-3  (1+2)*3  (1+2)/3  (1-2)+3  (1-2)-3  (1-2)*3  (1-2)/3
(1*2)+3  (1*2)-3  (1*2)*3  (1*2)/3  (1/2)+3  (1/2)-3  (1/2)*3  (1/2)/3

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


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 types, in other words), and c) it needs more type extensions.



{-# LANGUAGE
  MultiParamTypeClasses
, FunctionalDependencies
, FlexibleInstances
, UndecidableInstances
, TypeFamilies  , OverlappingInstances
  #-}

class Mcomp a ar b br | a br - b where
  mcomp :: a - (ar - br) - b

instance (a ~ ar, b ~ br) = Mcomp a ar b br where
  mcomp a f = f a

instance (Mcomp a ar b br) = Mcomp (x - a) ar (x - b) br where
  mcomp a f = \x - mcomp (a x) f


My question is: why doesn’t it work when I replace

instance (a ~ ar, b ~ br) = Mcomp a ar b br

with

instance Mcomp a a b b

? I thought that equal letters mean equal types…

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


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, but this will  
kill any performance, if needed.


In GHC.Prim — primitives addIntC# and subIntC#:


addIntC# :: Int# - Int# - (#Int#, Int##)
Add with carry. First member of result is (wrapped) sum; second member  
is 0 iff no overflow occured.



subIntC# :: Int# - Int# - (#Int#, Int##)
Subtract with carry. First member of result is (wrapped) difference;  
second member is 0 iff no overflow occured.


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


[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 instance declaration for (Show UTCTime)
In the second argument of `(=)', namely `print'
In the expression: getCurrentTime = print
In an equation for `it': it = getCurrentTime = print

…but when I create a file with `import Data.Time` in it, and load the file  
in GHCi,

everything works as expected.

Is it a bug in GHCi, or a feature? I’m using Haskell Platform 2012.2.0.1.

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


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 with haddock documentation created when installing
new packages with cabal on windows.
The generated html files have all links in the form
j:\Users\...\doc\...\xxx.html, but firefox says, it cannot open that
link.
Actually all links should be prefixed by file:///.

I wonder if this is only on windows so and if there is a solution to
this. Is there a cabal or haddock flag for this?


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


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
what one might get in a real specification from some client.


After taking a look at other solutions, I feel like I will have to explain
myself, so I’d better do that without prompting :)

  - nothing was said about meaningful error messages, so I didn’t bother.
  - I had decided against defining constants like  
`supplier_markup_percentage_modification`
separately; `PremiumSupplierIDs` and markup table are defined locally  
in the `calc`
function, too. The latter two issues are fixed in the next version, as  
someone

may consider them to be against elegance.
  - surprisingly, all solutions use explicit comparisons to determine the  
product
category. While it is okay for continuous ranges of codes, it doesn’t  
scale and

not really elegant. Fixed as well.

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


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 better to write an instance by yourself than use a deprecated package.  
Dead things should stay dead.


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


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

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


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
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 “computational effect”? If  
yes, then every computation is impure. If no, then what’s the difference  
between memory and hard drive?


By the way, the Data.HashTable is in IO monad. Is it impure? Would it be  
pure if designers had chosen to use ST instead?


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


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
not even in principle apply to any useful programming language, or a
definition of side effect that would have to apply every time a
program does anything - seems to me like an inane waste of time, to
put it mildly.


When one questions accepted definitions or beliefs, it is the sign of
their vagueness. To be honest, the definitions of “side effect” and
“purity” are vague indeed. I hope that eventually (probably in this
very discussion) they will be refined.

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


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, and
not being computable is just a property that they have.  Clearly this is
not a function at all.  It doesn't even have the general form of a
function: it has no input, so clearly it can't map each input value to a
specific output value.  Now, since it's not a function, it makes little
sense to even try to talk about whether it is computable or not (unless
you first define a notion of computability for something other than
functions).


Of course getAnIntFromUser is not a function. It is an instruction to  
computer.


Think of IO as a form of writing instructions to some worker (essentially,  
the kernel, which in its turn uses processor's io ports). You are asking  
this “worker” to change some global state.


Thus, your function “f” is a function indeed, which generates a list of  
instructions to kernel, according to given number.


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


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, we're  
saying: “here is a function which accepts Int and (sic!) returns Int, but  
it can also do IO, which is kinda unsafe. So we are marking it with ‘IO’  
letters, see? This means that this function is ‘impure’. And to prevent  
mixing pure things with impure things, compiler demands you to mark with  
IO every “function” which ‘uses’ IO”.


Functions don't use IO. Funtions return IO something. And functions  
returning IO are impure. That's all.



This is a valid concern... assigning a meaning to values of IO types
necessarily involves some very unsatisfying hand-waving about
indeterminacy, since for example IO actions can distinguish between
bottoms that are considered equivalent in the denotational semantics of
pure values (you can catch a use of 'error', but you can't catch
non-termination).  Nevertheless, I'm satisfied that to the extent that
any such meaning can be assigned, f will be a valid function on
non-bottom values.  Not perfect, but close.


Agree. The fact that IO actions can distinguish between bottoms,  
self-modify code, terminate non-terminable computations by rebooting the  
system, send killbots to the programmer's house and so on are extremely  
unsatisfying. That's IO for you.


The dirty impure bottom comparison which uses IO, though, is available  
only to already impure functions.


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


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
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 r2  1 then (a+1, n+2, r2) else (a+1, n+3, r3)
  where
a' = fromIntegral a
n' = fromIntegral n
r2 = r * (a'/(a'+1))**n' * (n'+1)*(n'+2)/(a'+1)^2
r3 = r2 * (n'+3) / (a'+1)

answers :: Array Int Int
answers = listArray (1, 100) (map snd3 $ iterate nextAns (1, 2, 2))
  where snd3 (a, b, c) = b
CODE END--

From these 1.5 seconds, 1 second is spent on doing GC. If I run it with  
-A200M, it executes for only 0.5 seconds (total).


Which is more interesting, when I use UArray instead of Array, it spends  
only 0.02 seconds in GC, but total running time is still 1.5 seconds.


Why are... these things?

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


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 OMIT_BOUNDS_CHECK
 {-# RULES
 ArrayIndex  arr ! i = unsafeAt arr (unsafeIndex (bounds arr) i)
  #-}
 #endif


Thanks!


 (?) = unsafeAt


Yes, but (!) was taken as an example. There is a lot of other
functions doing bounds checking... Creating replacements for every
single function is rather tedious.

The flag pragma also has other uses. For example, we can introduce an
overflow flag (check every operation with Int's for overflow) ,
which may be useful for debugging. In release version this flag will
be turned off.

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


[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 nice to have such  
option in GHC? Is it possible?


There is a problem: Haskell has a lot of array libraries. The only  
solution I see is a new FLAG pragma:


(!) :: Array i a - i - a
--definition

{-# FLAG boundsCheck (!) = unsafeAt #-}

It is similar to RULES pragma, but only fires when flag is set. To set the  
flag you need to complile with option -flags=boundsCheck. Also, the  
mantainers of vector library, bytestring library, repa library and so on  
will have to include such pragmas in their code.


I don't know about C++ preprocessor, though. Maybe this is already  
solvable with #define's...


Anyway, I have to say it once again: unsafeAt is ugly and Haskell is  
beautiful. Why high-performance code should be ugly?


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


[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 heard GHC 7.2.1 now includes module named GHC.Integer.Logarithms,  
but I can't find its description anywhere.


So, my question is: can I use full power of GMP's functions, and if I can  
— how?


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


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 easily, anyway).


I have found a manual on including additional primops in GHC (exactly this  
situation), but this requires modifying GHC's sources, which also does not  
allow using them with SPOJ.


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


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
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 special tricks, not the usual rule.


Scott Lawrence byt...@gmail.com писал(а) в своём письме Tue, 31 May 2011  
22:49:02 +0300:



I was under the impression that operations performed in monads (in this
case, the IO monad) were lazy. (Certainly, every time I make the
opposite assumption, my code fails :P .) Which doesn't explain why the
following code fails to terminate:

  iRecurse :: (Num a) = IO a
  iRecurse = do
recurse - iRecurse
return 1

  main = (putStrLn . show) = iRecurse

Any pointers to a good explanation of when the IO monad is lazy?


=== The long story ===

I wrote a function unfold with type signature (([a] - a) - [a]), for
generating a list in which each element can be calculated from all of
the previous elements.

  unfold :: ([a] - a) - [a]
  unfold f = unfold1 f []

  unfold1 :: ([a] - a) - [a] - [a]
  unfold1 f l = f l : unfold1 f (f l : l)

Now I'm attempting to do the same thing, except where f returns a monad.
(My use case is when f randomly selects the next element, i.e. text
generation from markov chains.) So I want

  unfoldM1 :: (Monad m) = ([a] - m a) - [a] - m [a]

My instinct, then, would be to do something like:

  unfoldM1 f l = do
next - f l
rest - unfoldM1 f (next : l)
return (next : rest)

But that, like iRecurse above, doesn't work.


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


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. It obviously is
not what is needed.

Prelude let launchMissiles = putStrLn UH OH  return 1
Prelude let iRecurse = launchMissiles  return 1
Prelude iRecurse
UH OH
1
Prelude
Looks like launchMissiles /does/ execute, even though x is (obviously)
never needed.


Oh, sorry. I was unclear. I have meant assuming IO is lazy, as Yves  
wrote.


And saying some hacks I meant unsafeInterleaveIO, which lies beneath the  
laziness of, for example, getContents.


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


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)).
   Cannot deduce (Show y) from context (Show (x, y)).

Um... seriously?

 From Prelude, we have

   Show x, Show y = Show (x, y)

So clearly it works in the forward direction. But apparently not in the  
reverse direction.


Is this a bug or a feature? (I.e., is there some obscure possibility I  
haven't thought of which means that doing the reverse inference would be  
incorrect?)


___
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] 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 in the standard
Haskell Platform or when it needs to be loaded from Hackage?


On Tue, May 17, 2011 at 9:08 AM, Benedict Eastaugh ionf...@gmail.com  
wrote:

cabal install primes?

http://hackage.haskell.org/package/primes
https://github.com/sebfisch/primes






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


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 somewhere a mark indicating  
that action was called. You can use IORefs.


import Data.IORef
import System.IO.Unsafe

putback x io = do
  m - readIORef r
  if m then io else (writeIORef r True  return x)
  where
r = unsafePerformIO $ newIORef False


Sergey Mironov ier...@gmail.com писал(а) в своём письме Sun, 15 May 2011  
17:33:51 +0300:



Hi Cafe. I wonder if it is possible to write a IO putback function
with following interface

putback :: a - IO a - IO a
putback x io = ???


where io is some action like reading from file or socket.
I want putback to build new action which will return x on first call,
and continue executing io after that.

Thanks in advance!
Sergey.


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


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:



lexOrder :: [Char] - [[Char]]
lexOrder s@[_] = s
lexOrder s =
 concat $ map (\n - h n) [0..((length z) - 1)]
 where z = sort $ nub s
   h :: Int - [String]
   h n = map (z!!n :) $ lexOrder $ filter (\c - lexI c z /=  
n) z



Euler.hs:8:18:
Couldn't match expected type `[Char]' with actual type `Char'
Expected type: [[Char]]
  Actual type: [Char]
In the expression: s
In an equation for `lexOrder': lexOrder s@[_] = s


It actually works, you have forgotten square brackets: lexOrder s@[_] =  
[s]   --not s!.


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


[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 for one second and then it crashes.

gloss-hello, strangely, is working perfectly.

I'm using Windows 7 (but on XP there is same behaviour), Haskell
Platform 2011.2, OpenGL 2.4.0.1, GLUT 2.2.2.0, Gloss 1.3.1.2.

At the first time, exampes didn't want to run at all, but I placed
glut32.dll from http://www.xmission.com/~nate/glut.html in my .dlls
folder. I tried another glut32.dll (from the Raincat game), but it
didn't change anything.

How can it be fixed?

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


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

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


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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 it's not enough. How can I use  
another value instead of 250? Should I write my own RootFinder instance,  
or findRoot function?


Thanks in advance.
— Artyom.

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


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 ± 20 different persons posting to this list (I just  
listed all the mail from Haskell-Cafe in my mail client and after 1.5  
hours of work I counted them all, so I can be slightly mistaken).


As only 1/2 of all haskellers post to the Cafe, and as I'm novice, I  
missed... OK, 6/7 of all haskellers (the number of haskellers grows over  
time, so there was little of them 10 years ago), 1200 * 2 * 7 = 16800  
haskellers.


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


[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: http://dl.dropbox.com/u/8662438/A%20State%20Monad%20Tutorial.pdf
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 t) = (putStrLn . show)

piMonte n = do
  (g1, g2) - split `fmap` getStdGen
  let r1 = r (n `div` 2) g1
  r2 = r (n `div` 2 + n `mod` 2) g2 in
return (ratio (r1 `par` (r2 `pseq` (merge r1 r2
  where
r n g = (length (filter id lAll), n)
  where
l = take n . randomRs (0, 1)
inCircle :: Double - Double - Bool
inCircle a b = a*a + b*b = 0.25
lAll = zipWith inCircle (l g1) (l g2)
(g1, g2) = split g
ratio :: (Int, Int) - Double
ratio (a, b) = fromRational (toInteger a % toInteger b * 16)
merge (a, b) (c, d) = (a + c, b + d)
--END

But it uses only on core:

C:\ghc --make -threaded Monte.hs -fforce-recomp
[1 of 1] Compiling Main ( Monte.hs, Monte.o )
Linking Monte.exe ...

C:\monte +RTS -N2 -s
monte +RTS -N2 -s
pi 1
n: 100
3.143616
   2,766,670,536 bytes allocated in the heap
   1,841,300 bytes copied during GC
   5,872 bytes maximum residency (1 sample(s))
  23,548 bytes maximum slop
   2 MB total memory in use (0 MB lost due to fragmentation)

  Generation 0:  5285 collections,  5284 parallel,  0.64s,  0.31s elapsed
  Generation 1: 1 collections, 1 parallel,  0.00s,  0.00s elapsed

  Parallel GC work balance: 1.00 (454838 / 454676, ideal 2)

MUT time (elapsed)   GC time  (elapsed)
  Task  0 (worker) :0.00s(  9.33s)   0.00s(  0.00s)
  Task  1 (worker) :0.63s(  9.33s)   0.00s(  0.00s)
  Task  2 (worker) :6.00s(  9.34s)   0.64s(  0.31s)
  Task  3 (worker) :0.00s(  9.34s)   0.00s(  0.00s)

  SPARKS: 1 (0 converted, 1 pruned)

  INIT  time0.02s  (  0.00s elapsed)
  MUT   time6.63s  (  9.34s elapsed)
  GCtime0.64s  (  0.31s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time7.28s  (  9.66s elapsed)

  %GC time   8.8%  (3.2% elapsed)

  Alloc rate416,628,033 bytes per MUT second

  Productivity  91.0% of total user, 68.6% of total elapsed

We see that our one spark is pruned. Why?

And another question. I compiled it also with -O:

C:\ghc --make -threaded Monte.hs -O -fforce-recomp
[1 of 1] Compiling Main ( Monte.hs, Monte.o )
Linking Monte.exe ...

C:\monte +RTS -N2 -s
monte +RTS -N2 -s
pi 1
n: 100
3.148096
   2,642,947,868 bytes allocated in the heap
   1,801,952 bytes copied during GC
   5,864 bytes maximum residency (1 sample(s))
  18,876 bytes maximum slop
   2 MB total memory in use (0 MB lost due to fragmentation)

  Generation 0:  5077 collections,  5076 parallel,  0.08s,  0.05s elapsed
  Generation 1: 1 collections, 1 parallel,  0.00s,  0.00s elapsed

  Parallel GC work balance: 1.00 (445245 / 444651, ideal 2)

MUT time (elapsed)   GC time  (elapsed)
  Task  0 (worker) :3.94s( 14.02s)   0.00s(  0.00s)
  Task  1 (worker) :0.00s( 14.02s)   0.00s(  0.00s)
  Task  2 (worker) :5.61s( 14.03s)   0.08s(  0.05s)
  Task  3 (worker) :0.00s( 14.05s)   0.00s(  0.00s)

  SPARKS: 1 (0 converted, 0 pruned)

  INIT  time0.02s  (  0.02s elapsed)
  MUT   time9.55s  ( 14.03s elapsed)
  GCtime0.08s  (  0.05s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time9.64s  ( 14.09s elapsed)

  %GC time   0.8%  (0.3% elapsed)

  Alloc rate276,386,705 bytes per MUT second

  Productivity  99.0% of total user, 67.7% of total elapsed

We see, that with -O, 2 worker threads were doing some job, but
overall performance is not better.
From one spark, zero - converted, zero - pruned. Is it a bug?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 Main where

import Data.List
import Data.Array.Unboxed
import qualified Data.Array.IArray as IArr
import Data.Ix

data SResult = Good | GoodProcess | Process | Bad

data SDPSearch a p r = SDPSearch (a - p - [a])   --expand
 (p - p)  --update
 (a - p - SResult)   --sort
 ([a] - r)--result

runSDPSearch :: SDPSearch a c b - [a] - c - b
runSDPSearch (SDPSearch e u s r) list p = r (rec list params)
  where
params = iterate u p
rec [] _ = []
rec (l:lp) pr@(n:np) = case s l n of
 Good- l : rec lp pr
 GoodProcess - l : (rec (e l n) np) ++ (rec lp pr)
 Process - (rec (e l n) np) ++ (rec lp pr)
 Bad - rec lp pr

main = do
  (a, b) - (break (== ' ')) `fmap` getLine
  print (knightTour (read a) (read b))

knightTour :: Int - Int - UArray (Int, Int) Int
knightTour a b = runSDPSearch (SDPSearch e u s r) [((1, 1), sArray)] 2
  where
size = a * b
range = ((1, 1), (a, b))
sArray = listArray range (1 : (replicate (size - 1) 0))
allTurns :: Array (Int, Int) [(Int, Int)]
allTurns = IArr.listArray range [turns x y | x - [1..a], y - [1..b]]
  where
shifts = [(1, 2),(1, -2),(2, 1),(2, -1),(-1, 2),(-1, -2),(-2,
1),(-2, -1)]
turns x y = [(x+i, y+j) | (i, j) - shifts, inRange range (x+i, y+j)]
e ((x, y), arr) p = [(t, arr // [(t, p)]) | t - changes]
  where
changes = [t | t - allTurns ! (x, y), arr ! t == 0]
s el p | p == size = Good
   | otherwise = Process
u = (+ 1)
r l | not (null l) = snd (head l)
| otherwise= error No solutions!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 dimension is 60 and the
 first is  18, it takes much longer,
...
 The magic change:

     e ((x, y), arr) p = [(t, arr // [(t, p)]) | t - changes]
       where
        legit ps = [t | t - allTurns ! ps, arr!t == 0]
         changes = map snd $ sort [(length $ legit t, t) | t - allTurns !
 (x, y), arr ! t == 0]

 investigate squares with fewer options first.


Wow! Thanks you!
By the way, I didn't notice the difference between (59, 59) and (60,
60) on my machine...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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
  take much much longer.
  With one little change, I get
  ...
  For a reason I don't understand, if the second dimension is 60 and the
  first is  18, it takes much longer,
 ...
  The magic change:
 
      e ((x, y), arr) p = [(t, arr // [(t, p)]) | t - changes]
        where
         legit ps = [t | t - allTurns ! ps, arr!t == 0]
          changes = map snd $ sort [(length $ legit t, t) | t -
  allTurns ! (x, y), arr ! t == 0]
 
  investigate squares with fewer options first.

 Wow! Thanks you!
 By the way, I didn't notice the difference between (59, 59) and (60,
 60) on my machine...

 Strangely,

 $ echo 62 59 | time ./knights  /dev/null
 0.10user 0.08system 0:00.17elapsed 101%CPU
 $ echo 65 59 | time ./knights  /dev/null
 0.08user 0.07system 0:00.17elapsed 96%CPU

 , so it's a thing of the second dimension predominantly (the size plays a
 small role, too).

 As I said, I don't understand it, but looking at the allocation figures:
 70*59: 97,970,072 bytes allocated in the heap
 18*60: 12,230,296 bytes allocated in the heap
 19*60: 2,374,148,320 bytes allocated in the heap
 19*61: 13,139,688 bytes allocated in the heap
 60*61: 71,771,324 bytes allocated in the heap
 61*61: 72,965,428 bytes allocated in the heap

 it seems that something is kicked out of the registers when the second
 dimension is 60 and the first  18.

 Very strange.

Maybe we were compiling with different options? I compiled with -O2
-fvia-C -optc-O3.
...
Oh, I know! I slightly changed the code.

import Data.Ord

e ((x, y), arr) p = [(t, arr // [(t, p)]) | t - changes]
  where
legit ps = [t | t - allTurns ! ps, arr ! t == 0]
changes = sortOn (length . legit) (legit (x, y))
sortOn = sortBy . comparing

My version gives answer for 60, 60 in one second. But if both
dimensions are 60, it won't finish.
Yes, very strange.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 field
 separators (e.g. spaces).


  #! /bin/sh
  ./prog --RTS ${1+$@}

 The longer specification above should work with whatever /bin/sh is around,
 whether it's Solaris /sbin/sh, FreeBSD's sh, general Linux bash,
 Debian/Ubuntu dash, etc.


And with Windows, of course :) Haskell is cross-platform, isn't it?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

 If you absolutely positively want all the rest of the options in a command
 line to go to the program (and not the RTS), use a ––RTS.

 $ ./prog +RTS --RTS +RTS

 ? (BTW, enclosing in quotes doesn't work anyway if the argument consists
 *only* of +RTS, same as with echo, echo -e doesn't output '-e' either).



So, if I type ./prog +RTS --RTS +RTS, the output will be +RTS. But
I want the output to be equal to the input IN ALL CASES, without any
quotes, additional options, etc. I want all the command line to go to
my program. How can I do it? (The only way I know now - hacking the
GHC. If there are no other ways, I'll do it.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 tried to write tail-recursive fact, fact as product [1..n] - fact2 is
quicker!


fact2 100 == fact 100 - I tested.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe