Re: [Haskell-cafe] Assembly EDSL in Haskell

2013-04-01 Thread Serguey Zefirov
You have fixed the type of list by move RAX RAX. Now it has type Instruction SNDREG SNDREG Make your Instruction a GADT and require that MOV should have appropriate constraints: {-# LANGUAGE DatatypeContexts, GADTs #-} data SREG = RIP data DREG = RBX data SNDREG = RAX data Instruction where

Re: [Haskell-cafe] Race Condition in threads

2012-12-18 Thread Serguey Zefirov
2012/12/18 mukesh tiwari mukeshtiwari.ii...@gmail.com: Hello All I have two questions. 1. I wrote this code to create 10 simultaneous threads. Could some one please tell me if this is correct or not ? incr_count :: MVar () - MVar Int - IO () incr_count m n = ( forM_ [ 1..1 ] $ \_ -

Re: [Haskell-cafe] C++

2012-12-11 Thread Serguey Zefirov
This array is for dynamic programming. You can diagonalize it into a list and use technique similar to the Fibonacci numbers. The resulting solution should be purely declarative. 2012/12/11 mukesh tiwari mukeshtiwari.ii...@gmail.com: Hello All I am trying to transform this C++ code in

[Haskell-cafe] Moscow Haskell Users Group (MskHUG) December meeting.

2012-12-03 Thread Serguey Zefirov
I would like to announce MskHUG December meeting and invite everyone interested. The meeting will take place December 13th, 20:00 to 23:30 in the nice conference center in centre of Moscow: http://www.nf-conference.ru/ The meeting's agenda is to start more intense discussions. Most probably,

Re: [Haskell-cafe] Wanted: Haskell binding for libbdd (buddy)

2012-08-20 Thread Serguey Zefirov
2012/8/20 Johannes Waldmann waldm...@imn.htwk-leipzig.de: Are there any Haskell bindings for BDD libraries (reduced ordered binary decision diagrams)? E.g., it seems buddy is commonly used http://packages.debian.org/squeeze/libbdd-dev and it has an Ocaml binding. Yes, there is

Re: [Haskell-cafe] class instances for kinds with finite ty constrs, does this make sense?

2012-06-15 Thread Serguey Zefirov
2012/6/8 Brent Yorgey byor...@seas.upenn.edu: On Thu, Jun 07, 2012 at 07:32:45PM +0100, ex falso wrote: we always have to put the class restriction (TupleLength l) there, even though all possible type constructors of [*] have a TupleLength instance defined! Yes, and this is a feature, for

Re: [Haskell-cafe] Large graphs

2012-05-20 Thread Serguey Zefirov
2012/5/20 Benjamin Ylvisaker benjam...@fastmail.fm: I have a problem that I'm trying to use Haskell for, and I think I'm running into scalability issues in FGL.  However, I am quite new to practical programming in Haskell, so it's possible that I have some other bone-headed performance bug

Re: [Haskell-cafe] Data Kinds and superfluous (in my opinion) constraints contexts

2012-05-17 Thread Serguey Zefirov
:48 AM, Serguey Zefirov sergu...@gmail.com wrote: I decided to take a look at DataKinds extension, which became available in GHC 7.4. My main concerns is that I cannot close type classes for promoted data types. Even if I fix type class argument to a promoted type, the use of encoding

[Haskell-cafe] Data Kinds and superfluous (in my opinion) constraints contexts

2012-05-06 Thread Serguey Zefirov
I decided to take a look at DataKinds extension, which became available in GHC 7.4. My main concerns is that I cannot close type classes for promoted data types. Even if I fix type class argument to a promoted type, the use of encoding function still requires specification of context. I consider

Re: [Haskell-cafe] Data.IntMap union complexity

2012-02-24 Thread Serguey Zefirov
2012/2/24 Clark Gaebel cgae...@csclub.uwaterloo.ca: Since insertion [2] is O(min(n, W)) [ where W is the number of bits in an Int ], wouldn't it be more efficient to just fold 'insert' over one of the lists for a complexity of O(m*min(n, W))? This would degrade into O(m) in the worst case, as

[Haskell-cafe] Composing analyses.

2012-01-04 Thread Serguey Zefirov
I am trying to create a stack of analyses. There are basic analyses then there are derived analyses that create a DAG of analyses. I thought I can express their relationship through type classes, but I failed. I've attached the source of my failure. Main points are below: getAnalysisResult ::

[Haskell-cafe] Hardware description in Haskell.

2011-12-11 Thread Serguey Zefirov
I would like to introduce my over-than-two years long project, HHDL: http://thesz.mskhug.ru/svn/hhdl/hackage/hhdl/ (I prefer to pronounce it as a ha-ha-dee-el, this way it is more fun) It allows one to create digital hardware description in Haskell and then generate VHDL code (Verilog is on the

Re: [Haskell-cafe] Hardware description in Haskell.

2011-12-11 Thread Serguey Zefirov
2011/12/11 Felipe Almeida Lessa felipe.le...@gmail.com: On Sun, Dec 11, 2011 at 10:52 AM, Serguey Zefirov sergu...@gmail.com wrote: scrutiny and critique by Haskell users who is into hardware description. A two years-old project is more than ready to be on Hackage.  It will sure make

Re: [Haskell-cafe] Disjunctive patterns

2011-12-08 Thread Serguey Zefirov
2011/12/8 Asger Feldthaus asger.feldth...@gmail.com: Haskell doesn't seem to support disjunctive patterns, and I'm having a difficult time writing good Haskell code in situations that would otherwise call for that type of pattern. Suppose for an example I have this data type: data T = Foo

Re: [Haskell-cafe] arr considered harmful

2011-11-01 Thread Serguey Zefirov
2011/11/1 Ryan Ingram ryani.s...@gmail.com: For example, I would love to be able to use the arrow syntax to define objects of this type: data Circuit a b where     Const :: Bool - Circuit () Bool     Wire :: Circuit a a     Delay :: Circuit a a     And :: Circuit (Bool,Bool) Bool     Or

[Haskell-cafe] Function code generation (Template Haskell).

2011-09-18 Thread Serguey Zefirov
The task is that I have some function and I need to create another function alongside with it. The second function is based on first one. As a matter of fact, I already did this with Template Haskell. TH is quite good at that task, because I can load my module in ghci and have both functions

[Haskell-cafe] Simple GADTs, type families and type classes combination with type error.

2011-07-22 Thread Serguey Zefirov
Why does GHC complains on the code below ? (I'll explain in a second a requirement to do just so) I get errors with ghc 6.12.1 and 7.0.2. - {-# LANGUAGE GADTs, TypeFamilies #-}

Re: [Haskell-cafe] Simple GADTs, type families and type classes combination with type error.

2011-07-22 Thread Serguey Zefirov
2011/7/22 Dan Doel dan.d...@gmail.com: On Fri, Jul 22, 2011 at 11:12 AM, Serguey Zefirov sergu...@gmail.com wrote: GHC cannot decide what instance of FuncVars to use. The signature of funcVars is:    funcVars :: FuncVars cpu = CPUFunc cpu - [String] This does not take any arguments

Re: [Haskell-cafe] Simple GADTs, type families and type classes combination with type error.

2011-07-22 Thread Serguey Zefirov
2011/7/22 Felipe Almeida Lessa felipe.le...@gmail.com: On Fri, Jul 22, 2011 at 12:12 PM, Serguey Zefirov sergu...@gmail.com wrote: Why does GHC complains on the code below ? (I'll explain in a second a requirement to do just so) I don't why =(.  But you can workaround by using  class CPU

Re: [Haskell-cafe] Probably type checker error.

2011-06-20 Thread Serguey Zefirov
, Serguey Zefirov wrote: Right now I write a quite heavy transformation of Haskell source code and found some strange behaviour of typechecker. Some prerequisites: -- dummy class. My own class is much bigger, but I -- could reproduce that behaviour with that class. class ToWires a -- a type

Re: [Haskell-cafe] Probably type checker error.

2011-06-20 Thread Serguey Zefirov
AM, Serguey Zefirov sergu...@gmail.com wrote: The fact is that (Num a) context works and (ToWires a, Num a) context doesn't. At least in 6.12.1. This still looks to me like a bug. 2011/6/19 Miguel Mitrofanov miguelim...@yandex.ru: Seems like let-generalization is at work here. Types of all

[Haskell-cafe] Probably type checker error.

2011-06-19 Thread Serguey Zefirov
Right now I write a quite heavy transformation of Haskell source code and found some strange behaviour of typechecker. Some prerequisites: -- dummy class. My own class is much bigger, but I -- could reproduce that behaviour with that class. class ToWires a -- a type with phantom type arguments.

Re: [Haskell-cafe] Probably type checker error.

2011-06-19 Thread Serguey Zefirov
NoMonomorphismRestriction. There is a proposal (from Big Simon) to remove let-generalization: http://research.microsoft.com/en-us/um/people/simonpj/papers/constraints/let-gen.pdf On 19 Jun 2011, at 18:26, Serguey Zefirov wrote: Right now I write a quite heavy transformation of Haskell source code

Re: [Haskell-cafe] Comment Syntax

2011-06-03 Thread Serguey Zefirov
2011/6/3 Guy guytsalmave...@yahoo.com: I wasn't proposing additional comment symbols; I'm proposing that anything beginning with -- is a comment. I use -- as a infix operator to describe types in Template Haskell. So I too oppose your proposal. ;)

[Haskell-cafe] Decimal type-level arithmetic.

2011-05-31 Thread Serguey Zefirov
I would like to present my version of type arithmetic with decimal encoding: http://thesz.mskhug.ru/svn/hhdl/TyleA.hs It is not worth Cabal package in its current state, but I hope it would be useful for someone. It is easy to use, just say Plus (D1 :. D2 :. D0) D8 to get a type of 128. Or you

Re: [Haskell-cafe] Decimal type-level arithmetic.

2011-05-31 Thread Serguey Zefirov
2011/6/1 Henning Thielemann lemm...@henning-thielemann.de: On Wed, 1 Jun 2011, Serguey Zefirov wrote: I would like to present my version of type arithmetic with decimal encoding: http://thesz.mskhug.ru/svn/hhdl/TyleA.hs How does it compare to  http://hackage.haskell.org/package/type-level

Re: [Haskell-cafe] Erlang's module discussion

2011-05-28 Thread Serguey Zefirov
2011/5/28 Alex Kropivny alex.kropi...@gmail.com: Erlang has the advantage of functions being the basic, composeable building block. Packages and modules are merely means to organize them, and mediocre means at that, so a better system is definitely a possibility. Haskell has the complication

Re: [Haskell-cafe] The Lisp Curse

2011-05-19 Thread Serguey Zefirov
I think this is much less applicable to Haskell than to Lisp. I think that most of intra-incompatibilities of Lisp stem from side effects. The rest is mostly due to (relatively) weak type system which let some errors slip. And remaining percent or two can be attributed to the power of Lisp. ;)

Re: [Haskell-cafe] The Lisp Curse

2011-05-19 Thread Serguey Zefirov
2011/5/19 Vo Minh Thu not...@gmail.com: 2011/5/19 Andrew Coppin andrewcop...@btinternet.com: http://www.winestockwebdesign.com/Essays/Lisp_Curse.html Some of you might have seen this. Here's the short version:  Lisp is so powerful that it discourages reuse. Why search for and reuse an

Re: [Haskell-cafe] how to generate source code from TH Exp?

2011-05-12 Thread Serguey Zefirov
Just pretty-print a Exp. It seems that show $ ppr exp will produce exactly what you need. The same goes for Dec (declarations), etc. 2011/5/12 Stefan Kersten s...@k-hornz.de: hi, i was wondering if it's possible to directly generate Haskell source code from a Template Haskell `Q Exp', i.e.

Re: [Haskell-cafe] Template Haskell reified type.

2011-05-10 Thread Serguey Zefirov
that is supposed to produce TupleT and ListT! Simon | -Original Message- | From: haskell-cafe-boun...@haskell.org [mailto:haskell-cafe-boun...@haskell.org] On | Behalf Of Serguey Zefirov | Sent: 09 May 2011 14:43 | To: haskell | Subject: [Haskell-cafe] Template Haskell reified

[Haskell-cafe] Template Haskell reified type.

2011-05-09 Thread Serguey Zefirov
Language.Haskell.TH.Type contains, among others, two constructors: TupleT Int and ListT. I can safely construct types using them, but reification returns ConT GHC.Tuple.(,) and ConT GHC.Types.[] respectively. This is not fair asymmetry, I think. Also, it took purity from one of my functions

[Haskell-cafe] Using Haskell to describe computer hardware.

2011-05-09 Thread Serguey Zefirov
http://thesz.mskhug.ru/svn/hhdl/ - main repository and http://thesz.mskhug.ru/svn/hhdl/examples/Simple.hs - three simple examples and http://thesz.mskhug.ru/svn/hhdl/MIPS-example/ - an attempt to describe MIPS-alike CPU using Haskell. Not yet done, it passes only simplest of tests (it fetches

Re: [Haskell-cafe] Python is lazier than Haskell

2011-04-27 Thread Serguey Zefirov
2011/4/27 Ketil Malde ke...@malde.org: Henning Thielemann lemm...@henning-thielemann.de writes: That Haskell is great because of its laziness is arguable, see Robert Harper's blog for all the arguing. (http://existentialtype.wordpress.com/) I think that author sin't quite right there.

Re: [Haskell-cafe] Stacking data types

2011-04-06 Thread Serguey Zefirov
I think I should suggest HList from Oleg Kiseliov. http://hackage.haskell.org/package/HList That way you will have something along those lines: -- fields descriptors: data Character data Gun data Armor data Life -- values for fields: data Vulcan = Vulcan { vulcanAmmoCount :: Int} data Player =

[Haskell-cafe] Two Haskell Platforms on single machine.

2011-03-30 Thread Serguey Zefirov
I had to use two Haskell Platforms at once in the Windows environment. We use Haskell Platform 2011.1 as our main build platform. It provide real benefits for code with GADTs so we ported most of our code there. Right now we cannot switch back or it would be quite a regress. We also have some

[Haskell-cafe] Regarding two platforms build error.

2011-03-30 Thread Serguey Zefirov
Haskell Platform 2010.1 with ghc 6.12.1 worked quite well. Problem solved. ;) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Type System vs Test Driven Development

2011-01-06 Thread Serguey Zefirov
2011/1/6 Arnaud Bailly arnaud.oq...@gmail.com: I would supplement this excellent list of advices with an emphasis on the first one: Test-Driven Development is *not* testing, TDD is a *design* process. Like you said, it is a discipline of thought that forces you first to express your intent

Re: [Haskell-cafe] Type System vs Test Driven Development

2011-01-06 Thread Serguey Zefirov
2011/1/6 Evan Laforge qdun...@gmail.com: QuickCheck especially is great because it automates this tedious work: it fuzzes out the input for you and you get to think in terms of higher-level invariants when testing your code. Since about six months ago with the introduction of JUnit XML support

[Haskell-cafe] GHC.Paths (libDir)

2011-01-04 Thread Serguey Zefirov
I am looking at GHC API examples page: http://www.haskell.org/haskellwiki/GHC/As_a_library One of examples use import GHC.Paths ( libDir) and mentions that it needs -package ghc-paths option. I tried the second example with latest Haskell Platform (Windows). I commented out libDir = /usr... as

[Haskell-cafe] GHC.Paths (libDir)

2011-01-04 Thread Serguey Zefirov
I figured that out, thank you if you are writing answer. ;) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Data.Typeable TypeRep Ord instance.

2010-12-30 Thread Serguey Zefirov
2010/12/30 Andreas Baldeau andr...@baldeau.net: instance Ord TypeRep where    compare t1 t2 =        compare            (unsafePerformIO (typeRepKey t1))            (unsafePerformIO (typeRepKey t2)) I think it would suffice. Thank you for a tip.

Re: [Haskell-cafe] Haskell Parse Tree

2010-12-21 Thread Serguey Zefirov
2010/12/21 Jane Ren j2...@ucsd.edu: Does anyone know how to get the parse tree of a piece of Haskell code? Any recommended documentation? ghc as a library? http://www.haskell.org/haskellwiki/GHC/As_a_library ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] An Haskell implementation of a sweep line algorithm for the detection of segments intersection

2010-12-06 Thread Serguey Zefirov
2010/12/6 vince vegga megatron...@gmail.com: Here is my Haskell implementation of the Shamos and Hoey algorithm for detecting segments intersection in the plane: http://neonstorm242.blogspot.com/2010/12/sweep-line-algorithm-for-detection-of.html Quite good, actually. Myself, I rarely write

Re: [Haskell-cafe] Reduceron: reduced to numbers.

2010-12-04 Thread Serguey Zefirov
2010/12/4 Henning Thielemann schlepp...@henning-thielemann.de: Serguey Zefirov schrieb: Of course, Reduceron in ASIC will require some cache memory, some controllers, etc. So it won't be that small, like 230K transistors. But, mzke it 2.3M transistors and it still be 2 orders of magnitude

[Haskell-cafe] Data.Typeable TypeRep Ord instance.

2010-12-04 Thread Serguey Zefirov
Why TypeRep does have equality and doesn't have ordering? It would be good to have that. Right now when I have to order two type representations I convert them to string and then compare. This is somewhat inefficient and not quite straightforward. ___

Re: [Haskell-cafe] Data.Typeable TypeRep Ord instance.

2010-12-04 Thread Serguey Zefirov
2010/12/5 Tianyi Cui tianyi...@gmail.com: Why should they? You can compare them in whatever way you like. And there isn't a natural/inherent sense of total order between types. I cannot compare then the way I'd like. ;) Consider the following: data BiMap a = BiMap { values :: Map Int a

Re: [Haskell-cafe] Digests

2010-12-03 Thread Serguey Zefirov
2010/12/3 Permjacov Evgeniy permea...@gmail.com: */me wrote it into to_read list. The problem is, however, that block ciphers are quite unfriendly to plain word8 streams. It is not a deadly problem, but i'd like to avoid block collections. All one-way hashes do block collections. This is

Re: [Haskell-cafe] Digests

2010-12-03 Thread Serguey Zefirov
2010/12/4 Permjacov Evgeniy permea...@gmail.com: near cryptographic) security. To quote Wikipedia again: The avalanche effect is evident if, when an input is changed slightly (for example, flipping a single bit) the output changes significantly (e.g., half the output bits flip). This simply

Re: [Haskell-cafe] Digests

2010-12-02 Thread Serguey Zefirov
2010/12/3 Permjacov Evgeniy permea...@gmail.com: The data integrity checks is well-known problem. A common soluting is use of 'checksums'. Most of them , however, are built in quite obfuscated manner (like md5) that results in ugly and error-prone implementations (see reference implementation

Re: [Haskell-cafe] Digests

2010-12-02 Thread Serguey Zefirov
2010/12/3 Permjacov Evgeniy permea...@gmail.com: Most of the time you can get away with usual block ciphers (and even with weaker parameters). There is a scheme that transforms block cipher into hash function: http://en.wikipedia.org/wiki/CRHF#Hash_functions_based_on_block_ciphers */me wrote

[Haskell-cafe] Reduceron: reduced to numbers.

2010-11-27 Thread Serguey Zefirov
I decided to calculate Reduceron's number of transistors (I had to, we have some argument here;). Reduceron allocate 14% of 17300 slices of Virtex-5 FPGA. If we assume that each slice correspond to 8 4-input NAND-NOT elements, we will get 2 4-input NAND. Each 4-input NAND contains 8

Re: [Haskell-cafe] Help me TH code.

2010-10-27 Thread Serguey Zefirov
2010/10/27 Andy Stewart lazycat.mana...@gmail.com: Hi all, I want use TH write some function like below:  data DataType = StringT                | IntT                | CharT  parse :: [(String,DataType)] - (TypeA, TypeB, ... TypeN) Example:  parse [(string, StringT), (001, IntT), (c,

Re: [Haskell-cafe] Help me TH code.

2010-10-27 Thread Serguey Zefirov
2010/10/27 Andy Stewart lazycat.mana...@gmail.com: Serguey Zefirov sergu...@gmail.com writes: I think that you should use TH properly, without compiler and logical errors. What actually do you want? I'm build multi-processes communication program. You don't need TH here, I think. You can

Re: [Haskell-cafe] Packaging a Gtk2hs based program for Windows

2010-10-07 Thread Serguey Zefirov
2010/10/7 Dmitry V'yal akam...@gmail.com: It sounds: How to make a neat Windows installer for a nice Gtk2hs program I wrote last week? How to solve the problem of dependency on GTK? Should I ask my users to install a GTK package or it would be better to package all the dynamic libraries needed

Re: [Haskell-cafe] Haskellers.com profiles: advice requested

2010-10-06 Thread Serguey Zefirov
2010/10/6 Michael Snoyman mich...@snoyman.com: Hi all, After finally getting OpenID 2 support worked out, I've now put up the Haskellers.com website[1]. Not all features are implemented yet, but the basics are in. Would it be possible to be able to login or consolidate two (or more)

Re: [Haskell-cafe] Haskellers.com profiles: advice requested

2010-10-06 Thread Serguey Zefirov
2010/10/6 Michael Snoyman mich...@snoyman.com: * How granular should we get? For web programming, for instance, should we ask about Yesod, Happstack, Snap, etc? I think that skill cloud would be nice so I can add my new skills (packages, programs, domain specific knowledge) as I acquire them

Re: [Haskell-cafe] I still cannot seem to get a GUI working under Windows.

2010-09-30 Thread Serguey Zefirov
2010/9/30 Andrew Coppin andrewcop...@btinternet.com: And even then, your developed application will only run on Windows boxes that have GTK+ installed (i.e., none of them). You can copy GTK+ DLLs with application. It works very well. ___

Re: [Haskell-cafe] Relaxing atomicity of STM transactions

2010-09-28 Thread Serguey Zefirov
2010/9/29 Tom Hawkins tomahawk...@gmail.com: In the embedded domain, this could be a fault monitor that reads a bunch of constantly changing sensors. I think that sensor reading belongs to IO, not STM. ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Help to create a function to calculate a n element moving average ??

2010-09-26 Thread Serguey Zefirov
2010/9/26 rgowka1 rgow...@gmail.com: Type signature would be Int - [Double] - [(Double,Double)] Any thoughts or ideas on how to calculate a n-element moving average of a list of Doubles? Let's say [1..10]::[Double] what is the function to calculate the average of the 3 elements?

Re: [Haskell-cafe] Scraping boilerplate deriving?

2010-09-14 Thread Serguey Zefirov
2010/9/14 Kevin Jardine kevinjard...@gmail.com: I would like to use some macro system (perhaps Template Haskell?) to reduce this to something like defObj MyType I've read through some Template Haskell documentation and examples, but I find it intimidatingly hard to follow. Does anyone has

Re: [Haskell-cafe] overloaded list literals?

2010-09-06 Thread Serguey Zefirov
2010/9/6 Bulat Ziganshin bulat.zigans...@gmail.com: Hello Johannes, Monday, September 6, 2010, 2:23:35 PM, you wrote: so how about using list syntax ( [], : ) for anything list-like (e.g., Data.Sequence)? i'vwe found my own proposal of such type:

Re: Re[4]: [Haskell-cafe] overloaded list literals?

2010-09-06 Thread Serguey Zefirov
2010/9/6 Bulat Ziganshin bulat.zigans...@gmail.com: Hello Serguey, Monday, September 6, 2010, 8:16:03 PM, you wrote: Basically, you - and others, - propose to add another class isomorphic to already present lists. I think, most benefits of that class can be achieved by using list conversion

[Haskell-cafe] Haskell Platform on Windows - cabal update problems.

2010-09-04 Thread Serguey Zefirov
I've installed recent Haskell Platform and tried to wrap my head around cabal to finally figure out how to use it. First thing I bumped into is that cabal.exe does not know about any remote repositories, even about hackage. So after googling I found that I should add a line remote-repo:

Re: [Haskell-cafe] Re: Haskell Platform on Windows - cabal update problems.

2010-09-04 Thread Serguey Zefirov
2010/9/5 Mikhail Glushenkov the.dead.shall.r...@gmail.com: Try removing the 'Application Data/cabal' directory and running 'cabal update'. You probably made a syntax error in the config file. You are clearly a magician. ;) Now it works flawlessly. Thank you very much.

Re: [Haskell-cafe] Announce: lhae

2010-09-03 Thread Serguey Zefirov
2010/9/3 abau a...@imn.htwk-leipzig.de: lhae is a spreadsheet program. It features a simple formula language and some basic statistical methods, like descriptive statistics and pivot tables. Interesting. You had selected wxWidgets because of what? Also, how long did it took (especially GUI

[Haskell-cafe] Ordering TypeRep from Data.Typeable.

2010-08-26 Thread Serguey Zefirov
I think, that TypeRep type from Data.Typeable needs Ord class instance. It is unnecessary, but is handy when needed. My use case follows. I try to create graph whose node and arc labels are differently typed. So I can add Int node, Float node and link them by Conversion arc. Right now I am

Re: [Haskell-cafe] Higher-order algorithms

2010-08-23 Thread Serguey Zefirov
2010/8/23 Eugene Kirpichov ekirpic...@gmail.com: For example, parser combinators are not so interesting: they are a bunch of relatively orthogonal (by their purpose) combinators, each of which is by itself quite trivial, plus not-quite-higher-order backtracking at the core. This is only if

Re: [Haskell-cafe] Fast Integer Input

2010-08-23 Thread Serguey Zefirov
2010/8/23 200901...@daiict.ac.in: This function takes 1.8 seconds to convert 2000 integers of length 10^13000. I need it to be smaller that 0.5 sec. Is it possible? 2000 integers of magnitude 10^13000 equals to about 26 MBytes of data (2000 numbers each 13000 digits long). Rounding 1.8

Re: [Haskell-cafe] Fast Integer Input

2010-08-23 Thread Serguey Zefirov
2010/8/23 Bertram Felgenhauer bertram.felgenha...@googlemail.com: Serguey Zefirov wrote: The timings seem about right. Thank you for letting me know about divide-and-conquer variant. But I am still amuzed that producing 1200 words of data from 13Kbytes of text took those little 200 cycles

Re: [Haskell-cafe] Support for lock-free/wait-free programming?

2010-08-17 Thread Serguey Zefirov
2010/8/17 Gregory Collins g...@gregorycollins.net: Does GHC expose any primitives for things like atomic compare-and-swap? I think that STM could qualify as LL/SC. It does LL with TVars and bulk SC with transaction commit. ;) ___ Haskell-Cafe mailing

Re: [Haskell-cafe] Combining Gtk2hs and Fieldtrip

2010-08-08 Thread Serguey Zefirov
Gtk2hs has an OepnGL binding. So you can create OpenGL context and draw there. I don't think you will still be able to use parallel threads, but path to hardware renderer will be shorter for sure. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] Is there any experience using Software Transactional Memory in substantial applications?

2010-08-08 Thread Serguey Zefirov
Recently we discussed Haskell and especially types in Russian part of LiveJournal and of course we talk about STM. My opponent gave me that link: http://logicaloptimizer.blogspot.com/2010/06/so-microsofts-experiments-with-software.html It says that performance with STM in Microsoft Research was

Re: [Haskell-cafe] Is there any experience using Software Transactional Memory in substantial applications?

2010-08-08 Thread Serguey Zefirov
in substantial applications? To: Serguey Zefirov sergu...@gmail.com This first papers is the first that describes the preliminary haskell implementation and the performance data says that STM scales well with the number of CPU cores  Blocking does not scale, as expected. http

Re: [Haskell-cafe] Is there any experience using Software Transactional Memory in substantial applications?

2010-08-08 Thread Serguey Zefirov
2010/8/8 Johnny Morrice sp...@killersmurf.com: My opponent gave me that link: http://logicaloptimizer.blogspot.com/2010/06/so-microsofts-experiments-with-software.html I enjoy the article you linked but I sort of skimmed it because it was a little boring, however its main point seem to be:

[Haskell-cafe] Type Families: deleting from HList.

2010-07-31 Thread Serguey Zefirov
Is it possible to delete an element from heterogenous list using type families alone? I can do it using multiparameter type classes: class Del a list result instance Del a (a,list) list instance Del a list list' = Del a (a',list) list' instance Del a () () I tried to express the same using type

Re: [Haskell-cafe] Re: Microsoft's Singularity Project and Haskell

2010-07-31 Thread Serguey Zefirov
2010/7/31 David Leimbach leim...@gmail.com: Haskell's great and all but it does have a few warts when it comes to how much real trust one  should put into the type system. Some compromises still exist like unsafePerformIO that you can't detect simply by looking at the types of functions.

Re: [Haskell-cafe] Template Haskell sees into abstract data types

2010-07-28 Thread Serguey Zefirov
2010/7/28 Jonas Almström Duregård jonas.dureg...@gmail.com: Hi, I cannot write classes that see into internal structure. For example, I cannot write my own (de)serialization without using from/toAscList. Actually I don't believe you can do this with TH either. TH splices code into the

Re: [Haskell-cafe] Template Haskell sees into abstract data types

2010-07-28 Thread Serguey Zefirov
2010/7/28 Simon Peyton-Jones simo...@microsoft.com: I assume you've seen http://hackage.haskell.org/trac/ghc/ticket/4222 There are non-obvious design choices here Yes, I've seen that. Right now I just cannot grok it fully. I feel like I should share my current understanding with cafe, so I

Re: [Haskell-cafe] Lists and monads

2010-07-26 Thread Serguey Zefirov
2010/7/26 Kevin Jardine kevinjard...@gmail.com: I suspect that things are not quite as difficult as they appear, however, but cannot find any tutorials on monadic list manipulation. I'd suggest that you get as many pure values as possible from impure world, apply to them easy to use pure

Re: [Haskell-cafe] Design for 2010.2.x series Haskell Platform site

2010-07-17 Thread Serguey Zefirov
2010/7/17 Don Stewart d...@galois.com: Here's a first cut in the repo with the new design converted to CSS    http://code.haskell.org/haskell-platform/download-website/ If anyone would like to clean it up further, please send me patches to the style.css file or index.html. I have big fonts

Re: [Haskell-cafe] trees and pointers

2010-07-15 Thread Serguey Zefirov
2010/7/15 Sergey Mironov ier...@gmail.com: 2010/7/15 Serguey Zefirov sergu...@gmail.com: 2010/7/14 Sergey Mironov ier...@gmail.com: Hi cafe! I have a question of C-to-Haskell type:) Imagine web application wich allows users to browse some shared filesystem located at the server. Application

Re: [Haskell-cafe] trees and pointers

2010-07-14 Thread Serguey Zefirov
2010/7/14 Sergey Mironov ier...@gmail.com: Hi cafe! I have a question of C-to-Haskell type:) Imagine web application wich allows users to browse some shared filesystem located at the server. Application stores every users's position within that filesystem (current directory or file). In C

Re: [Haskell-cafe] Re: Float instance of Data.Bits

2010-07-09 Thread Serguey Zefirov
2010/7/9 Ertugrul Soeylemez e...@ertes.de: Sam Martin sam.mar...@geomerics.com wrote: Nobody would really need the operations (we have integer types and UArray Int Bool for bit manipulation), and they would most likely be very slow. They won't be slow using SSE2 or something. I can see where

Re: [Haskell-cafe] Re: Float instance of Data.Bits

2010-07-09 Thread Serguey Zefirov
2010/7/9 Sam Martin sam.mar...@geomerics.com: Some operations wouldn't make much sense with Float, for instance the 'complement' function.  What should it return?  Also note that bit manipulation functions could cover only a small window of the value range.  So it could happen that x .|. y =

Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Serguey Zefirov
The thing that is hard for me to understand is how, in a functional paradigm, to update the entire Doc by chasing down every tie and making all necessary updates. This looks like one of graph algorithms. Notes are nodes, ties are arcs. Measures, etc are parts of node label. soundedEnd

Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Serguey Zefirov
Actually, it would be wise to parametrize Item with computed attributes so that you can clearly distinguish between documents where soundedEnd is set from documents where it is not. Ah, this sounds like something I am looking for... parameterizing Item with the computed attributes. But I am

[Haskell-cafe] Template Haskell sees into abstract data types

2010-07-03 Thread Serguey Zefirov
Data.Map.Map and Data.Set.Set are exported abstractly, without exposing knowledge about their internal structure. I cannot directly create my own class instances for them because of that. But I found that I can write Template Haskell code that could do that - those data types could be reified

Re: [Haskell-cafe] Template Haskell sees into abstract data types

2010-07-03 Thread Serguey Zefirov
I cannot directly create my own class instances for them because of that. But I found that I can write Template Haskell code that could do that - those data types could be reified just fine. Huh? Sure you can write class instances for them. , | instance SizeOf (Map k v) where |

Re: [Haskell-cafe] How easy is it to hire Haskell programmers

2010-06-30 Thread Serguey Zefirov
On Wed, Jun 30, 2010 at 4:34 PM, Paul Johnson p...@cogito.org.uk wrote: I'm starting to see job adverts mentioning Haskell as a nice to have, and even in some cases as a technology to work with. However right now I'm looking at it from the other side.  Suppose someone wants to hire a Haskell

Re: [Haskell-cafe] How does one get off haskell?

2010-06-24 Thread Serguey Zefirov
2010/6/17 Günther Schmidt gue.schm...@web.de: BTW this is not meant as a fun post, I'm actually quite serious, ie. I need money, only way of getting it is doing Java, C# or PHP. So how does one get off haskell? Are there people in similar situations that have managed? How did you do it? I

Re: [Haskell-cafe] TDD in Haskell

2010-05-25 Thread Serguey Zefirov
I'm doing TDD in pretty much all of the languages that I know, and I want to introduce it early in my Haskell learning process. I wonder though, if there's some established process regarding TDD, not unit testing. TDD can be deciphered as Type Driven Design, and right now not so many languages

Re: [Haskell-cafe] cabal-install

2010-05-19 Thread Serguey Zefirov
2010/5/19 Ivan Lazar Miljenovic ivan.miljeno...@gmail.com: Serguey Zefirov sergu...@gmail.com writes: Why there is no switch to turn off any use of proxy in cabal-install? Or to supply username/password pair in command line. I have a strange situation: wget works like charm ignoring proxy (I

Re: [Haskell-cafe] Bug with [Double]

2010-05-19 Thread Serguey Zefirov
2010/5/19 Erik de Castro Lopo mle...@mega-nerd.com: Dmitry Olshansky wrote: It seems that I saw something like this in Cafe recevtly. But I am not sure... In GHC 6.12.1 (Platform 2010 on Windows Vista) I have snip Any comments? The problem you point out is not a problem with Haskell,

Re: [Haskell-cafe] cabal-install

2010-05-19 Thread Serguey Zefirov
I tried it and it didn't work. I don't know reason, though, maybe it was because my current password not entirely alphanumeric. Shouldn't matter as long as you put it within quotes. I imagine things will go wrong if it includes an @... urlencoding is probably a smart idea. Thank you very

[Haskell-cafe] cabal-install

2010-05-18 Thread Serguey Zefirov
Why there is no switch to turn off any use of proxy in cabal-install? Or to supply username/password pair in command line. I have a strange situation: wget works like charm ignoring proxy (I downloaded Cabal and cabal-install to investigate the problem using wget), Firefox works like charm

Re: [Haskell-cafe] Performance Issue

2010-05-18 Thread Serguey Zefirov
2010/5/18 Richard Warburton richard.warbur...@gmail.com: GHC performs almost no common subexpression elimination, the reasons being that it can introduce space leaks and undesired extra laziness. Is there any way to encourage it to do so, for example compilation flags?  Or is it generally best

Re: [Haskell-cafe] Re: Hackage accounts and real names

2010-04-06 Thread Serguey Zefirov
2010/4/6 r...@ro-che.info: On Tue, 06 Apr 2010 20:06:27 +1000, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote: I've been over this thread and couldn't see anywhere where you'd made an attempt to refute these arguments, so I guess you take them as solid. On the other hand, every

Re: [Haskell-cafe] Apparently, Erlang does not have a static type system, since with hot code loading, this is intrinsically difficult.

2010-04-04 Thread Serguey Zefirov
2010/4/4 Casey Hawthorne cas...@istar.ca: Apparently, Erlang does not have a static type system, since with hot code loading, this is intrinsically difficult. Apparently, this is doable with proper engineering even for such an unsafe language as C: http://www.cs.umd.edu/projects/PL/dsu/

Re: [Haskell-cafe] More Language.C work for Google's Summer of Code

2010-03-30 Thread Serguey Zefirov
I tried to devise a C preprocessor, but then I figured out that I could write something like that: --- #define A(arg) A_start (arg) A_end #define A_start this is A_start definition. #define A_end this is A_end definition. A ( #undef A_start #define A_start A_end )

  1   2   >