Re: [Haskell-cafe] "Out of memory" if compiled with -O2, why?

2010-12-04 Thread Bulat Ziganshin
Hello Jason,

Wednesday, December 1, 2010, 8:54:58 PM, you wrote:


> I'm using ghc7 here.  If I run your program with -O2, it takes 1943 MB of 
> memory max.
> If I comment out everything except g then with -O2 it takes 1521 MB.

> I'm not sure where the extra 400 MB of memory are going.

i think, it's because memory isn't collected immediately, so in first
case you just have more garbage hanging around. if you need to measure
real workset of your program, you should apply very aggressive (and
slow) garbage collection settings

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com


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


Re: [Haskell-cafe] Same compiled program behaving differently when called from ghci and shell

2010-11-21 Thread Bulat Ziganshin
Hello Bruno,

Sunday, November 21, 2010, 8:49:52 AM, you wrote:

> ghc --make ftest2.hs

may be your versions of ghc and (win)ghci are different? the behavior
was changed in latest versions afaik


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] "Haskell is a scripting language inspired by Python."

2010-11-09 Thread Bulat Ziganshin
Hello Gregg,

Tuesday, November 9, 2010, 2:12:12 AM, you wrote:


 >> Doesn't COBOL have significant layout anyway as an inspiration to
 >> both? 

> Yes and no.  What it actually has relates strongly to punched cards
>  and is more like assemblers of the day.

i never programmed in COBOL, but afaik data structures usually was
organized this way - together with level numbers at left. it was just
easier to read it this way


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Most popular haskell applications

2010-11-05 Thread Bulat Ziganshin
Hello Ivan,

Saturday, November 6, 2010, 4:05:38 AM, you wrote:

> Possible candidates:
> * GHC
> * XMonad
> * Darcs

for me, darcs and ghc are programmer's instruments. xmonad is real
application, having some utility outside of programmers community.
i'm looking for utility of haskell for "real world". i know that it's
used in-house (as in Deutsche Bank) or to build some solutions. what
i'm looking for is shareware or so, things that are usually written with
Delphi-class languages

> Of course, it's hard to tell: do people actually use those packages
> once they've downloaded them?  How do you measure downloads when some
> people use downstream binaries?

for windows application download counter is good enough measure, at
least while we compare one program with another. unfortunately, xmonad
isn't a windows app :D


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


[Haskell-cafe] Most popular haskell applications

2010-11-05 Thread Bulat Ziganshin
Hello haskell,

people, are you know haskell apps that has more than 50k downloads per
month (or more than 25k users) ?

-- 
Best regards,
 Bulat  mailto:bulat.zigans...@gmail.com

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


[Haskell-cafe] Re[2]: Rigid types fun

2010-11-05 Thread Bulat Ziganshin
Hello Mitar,

Friday, November 5, 2010, 2:08:52 PM, you wrote:

> I would like to call it like "create (Axon undefined) (AxonAny
> undefined)" and get in that case "Nerve (Axon a) (AxonAny b)" as a
> result. If I would call it like "create (AxonAny undefined) (AxonAny
> undefined)" I would get "Nerve (AxonAny a) (AxonAny b)" as a result.
> And so on.

look into HsLua sources. it does something like you asking (converting
return type into sequence of commands) so it mau be what you are
looking for. it uses typeclasses for this effect. the same technique
used in haskell printf implementation afaik

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


[Haskell-cafe] Re: Rigid types fun

2010-11-05 Thread Bulat Ziganshin
Hello Mitar,

Friday, November 5, 2010, 12:45:21 PM, you wrote:

> from <- newChan
> for <- newChan
> let nerve = Nerve (Axon from) (AxonAny for)

create = do from <- newChan
for <- newChan
return$ Nerve (Axon from) (AxonAny for)

main = do nerve <- create
  ...


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] What is simplest extension language to implement?

2010-11-02 Thread Bulat Ziganshin
Hello Permjacov,

Tuesday, November 2, 2010, 9:04:00 AM, you wrote:

> Let us think, that we need some scripting language for our pure haskell
> project and configure-compile-run is not a way. In such a case a
> reasonably simple, yet standartized and wide known language should be
> implemented. What such language may be?

http://www.haskell.org/haskellwiki/HsLua
or python

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Converting Values Between Lua And Haskell

2010-10-24 Thread Bulat Ziganshin
Hello aditya,

Sunday, October 24, 2010, 8:05:55 AM, you wrote:

HsLua page is nothing more but my fantasy about future HsLua
development :)  you may find even XXX type where i don't found good
name :)

> Hi all,
> The HsLua page [1] says that Int,Double,String,Bool,[a] and [(a,b)]
> types can be converted to and from Lua values. However the on hslua
> API page I don't see a StackValue instance [2] for [a] or [(a,b)]. Am I 
> missing something?
>  -deech

> [1]
> http://www.haskell.org/haskellwiki/HsLua#Exchanging_data_between_Haskell_and_Lua_worlds
> [2]
> http://hackage.haskell.org/packages/archive/hslua/latest/doc/html/Scripting-Lua.html#t:StackValue
>   


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] concurrency vs. I/O in GHC

2010-10-23 Thread Bulat Ziganshin
Hello Claude,

Saturday, October 23, 2010, 11:57:23 PM, you wrote:

>> Is that true? The last time we discussed this in Haskell Cafe the
>> conclusion I drew from the discussion was that unsafe foreign functions
>> block the current thread but not any other thread.

> The conclusion I drew was that "unsafe" foreign functions block the 
> current "capability" (OS thread) and any "threads" (Haskell forkIO etc)
> currently scheduled on that capability, but other capabilities and 
> threads continue executing as normal.

yes, it blocks entire capability but afaik only one haskell thread can
be scheduled on some capability at any concrete moment


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] readProcess exception

2010-10-22 Thread Bulat Ziganshin
Hello Leskó,

Friday, October 22, 2010, 1:50:54 AM, you wrote:

> I run into a problem with readProcessWithExitCode (from System.Process
> module). Basically what i want is to start an exe file, giving it some
> input on stdin and receiving the results on stdout. But id the stdin and

look for other functions in the library. one that you need should read
and write data simultaneously, for example by using separate thread


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] concurrency vs. I/O in GHC

2010-10-22 Thread Bulat Ziganshin
Hello John,

Monday, October 18, 2010, 8:15:42 PM, you wrote:

> If anyone is listening, I would very much like for there to be a
> mechanism by which external functions can be called "unsafe"-ly, but
> without blocking all other Haskell threads.  I have code that does this:

+RTS -N2

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Lambda-case / lambda-if

2010-10-04 Thread Bulat Ziganshin
Hello Ketil,

Monday, October 4, 2010, 11:30:48 AM, you wrote:
>> Prelude> (if then "Haskell" else "Cafe") False

lambda-if is easily implemented in terms of usual functions.
and we even have one named bool:

bool: Bool -> a -> a -> a

lambda-case cannot be implemented as a function since we need
matching ability of "case"


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Big Arrays

2010-10-04 Thread Bulat Ziganshin
Hello John,

Monday, October 4, 2010, 7:57:13 AM, you wrote:

> Sure it does; a 32-bit system can address much more than 2**30
> elements. Artificially limiting how much memory can be allocated by
> depending on a poorly-specced type like 'Int' is a poor design
> decision in Haskell and GHC.

are you understand that the "poor design decision" makes array access
several times faster and doesn't limit anything except for very rare huge
Bool arrays?


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Big Arrays

2010-10-03 Thread Bulat Ziganshin
Hello Henry,

Sunday, October 3, 2010, 7:54:49 PM, you wrote:

> It looks like array ranges can only be Ints, and not Int64 or Word64 types.

yes, it's Int internally got efficiency reasons. you can do your own
implementation to override this limit :)


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] EDSL for Makefile

2010-10-03 Thread Bulat Ziganshin
Hello C,

Sunday, October 3, 2010, 6:59:25 PM, you wrote:

> Thanks Neil,

>> main = do
>>  want ["file1"]
>>  "file1" *> \x -> do
>>    need ["file2"]
>>    putStrLn "Hello"
>>    putStrLn "World"

> What if I want to mention "file1" only once?

mention_only_once file action = do
  want [file]
  file *> action

main = mention_only_once "file1" $ \x -> do need ["file2"]
    putStrLn "Hello"
    putStrLn "World"




-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


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

2010-10-02 Thread Bulat Ziganshin
Hello Heinrich,

Saturday, October 2, 2010, 1:36:48 PM, you wrote:

> Would you put a flattr button [1] on the wxHaskell page? This way,
> people like me would be able to show their appreciation by donating a

this page doesn't describe how to pay and how to got the money
received. if Jeremy lives in "right" country, i suggest to use PayPal
donations system. it allows to pay by credit card and then receive money
to author's credit card

PayPal provides you the donation button like one i used at
http://freearc.org/Donations.aspx 


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Why can't libraries/frameworks like wxHaskell/gtk2hs/... be used with newer versions of ghc/wxWidgets/GTK+/... ?

2010-09-27 Thread Bulat Ziganshin
Hello caseyh,

Monday, September 27, 2010, 9:55:14 PM, you wrote:

> Why can't libraries/frameworks like wxHaskell/gtk2hs/... be used with
> newer versions of ghc/wxWidgets/GTK+/... ?

because you don't compile from source code. ghc does massive inlining
so parts of old ghc libraries are compiled into gtk2hs object files


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] FFI and concurrency

2010-09-10 Thread Bulat Ziganshin
Hello Johannes,

Friday, September 10, 2010, 2:25:58 PM, you wrote:

just forkIO in threaded RTS works for me. try:

main = do forkIO expensiveCalc
  forkIO expensiveCalc
  forkIO expensiveCalc
  expensiveCalc

> What's the story with FFI calls and concurrency?

> I have an expensive calculation performed
> by some C function, which I call from Haskell land.
> (This works like a charm.)

> I have several cores available. How could I run
> several of these calculations in parallel?

> Thanks, Johannes.


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


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Style and a problem

2010-09-09 Thread Bulat Ziganshin
Hello Wanas,

Friday, September 10, 2010, 12:55:14 AM, you wrote:
> a) I want to write a function  that generates lists of lists of
> size $n$. All having the property that  sum lst = sum [1..n].
>  a-1) After that, I want to remove all permutations. My idea of

you have very interesting questions. hopefully it was already answered
at http://www.haskell.org/haskellwiki/Homework_help


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Re: ghc HEAD

2010-09-07 Thread Bulat Ziganshin
Hello Brandon,

Tuesday, September 7, 2010, 8:37:32 PM, you wrote:

> I'd call this incomplete because programs compiled with RTS options enabled
> are still insecure.

> The correct fix is to ignore GHCRTS and die on +RTS *when setuid*.  Since

i strongly agree


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Operator precedence

2010-09-06 Thread Bulat Ziganshin
Hello michael,

Monday, September 6, 2010, 9:00:32 PM, you wrote:

> Is there a handy list of operators and their precedence somewhere?

unlike most languages, operators are user-definable in haskell. so
there is no comprehensive list

any function with two arguments van be used as operator:

a `min` b

any operator may be defined or used as a function:

(&&) a b = ...

main = print ((&&) True False)


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


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

2010-09-06 Thread Bulat Ziganshin
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 and RULE pragma.

what i propose should allow to convert algorithm dealing with strings
into algorithm dealing with ByteStrings, simply by changing import
statement

it's a cute goal - keep Haskell strings easy of use but add ByteString
performance


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


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

2010-09-06 Thread Bulat Ziganshin
Hello Serguey,

Monday, September 6, 2010, 7:57:46 PM, you wrote:

>> http://www.mail-archive.com/haskell-cafe@haskell.org/msg15656.html

> Will Data.Map with its' empty, insert, findMin, etc, "methods" conform
> to your proposed type?

but Data.Map isn't sequential container. instead, it maps arbitrary
keys to values


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] overloaded list literals?

2010-09-06 Thread Bulat Ziganshin
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:
http://www.mail-archive.com/haskell-cafe@haskell.org/msg15656.html


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


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

2010-09-06 Thread Bulat Ziganshin
Hello Stefan,

Monday, September 6, 2010, 3:47:11 PM, you wrote:

> In general, it is kind of unfortunate that type classes and type
> constructors share a namespace, even though there is no way to ever mix them 
> up.

btw, i also had proposal to automatically convert typeclasses used in
type declarations into constraints, so that:

putStr :: StringLike -> IO ()
treated as
putStr :: StringLike s => s -> IO ()

and

length :: ListLike a -> Int
treated as
length :: ListLike (c a) => c a -> Int

Together with proposals i mentioned previously, it will allow to treat
existing code dealing with lists/strings as generic code working
with any sequential container type

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] overloaded list literals?

2010-09-06 Thread Bulat Ziganshin
Hello Johannes,

Monday, September 6, 2010, 2:23:35 PM, you wrote:

i had such idea several years ago and proposed to name class ListLike.
this class was finally implemented by John Goerzen and it does
everything we can w/o changing language

the main thing about literals is that they need to be recognized also
at left side of equations, so that

length (s:xs) = 1 + length xs
length [] = 0

will work for ByteStrings and arrays like it work for list. if it will
be implemented, then most programs manipulating on lists/strings, can
be converted to more efficient ones simply by replacing imports

Haskell 1.0 views may be the way to go, virtually converting other
containers to lists, back and forth. of course, only if these virtual
conversions will be optimized away by smart compiler



> I think left-biased (= singly linked) lists
> are much overrated in Haskell coding (and teaching).

> The language (syntax and Prelude) makes it just too easy to use them,
> and old habits (from LISP) die hard.

> Sure, lists serve a purpose: 
> * they model (infinite, lazy) streams, used
>   in the producer/transformer/consumer pattern
> * they are an algebraic data type,
>   so you can use them to teach recursion ((co-)induction);
>   
> but more often, lists are (mis-)used when actually
> * you want some efficiently index-able and concat-able sequence type
> * or you don't need the indexing, just membership, so you actually want 
> Data.Set
>   (disregarding strictness and unwanted Ord instances for the moment).
>   It is an empirical law that in 90 percent of the cases where 
>   a computer science student says "list" he means "set".
> * you avoid/forget to tell your students about algebraic data types in 
> general.


> Hypothetically now ... 

> We have overloaded numerical literals (Num.fromInteger)
> and we can overload string literals (IsString.fromString),
> so how about using list syntax ( [], : )
> for anything list-like (e.g., Data.Sequence)?

> Of course some "minor details" would need to be worked out,
> like what methods should go in the hypothetical "class IsList"
> (is is Foldable?) and what to do about pattern matching
> (perhaps we don't need it?)

> IIRC there was a time when list comprehension 
> would actually mean monad comprehension 
> (when there was no "do" notation)
> but that's not what I'm getting at here. Or is it?
> Do we have a "Haskell museum" of ideas from the past?


> Best - J.W.


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


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Arrow transformers: how to make them wright?

2010-08-31 Thread Bulat Ziganshin
Hello Permjacov,

Tuesday, August 31, 2010, 10:07:38 PM, you wrote:

>  what operations should be in arrow transformer class?

oh, these Russians :)


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] On to applicative

2010-08-31 Thread Bulat Ziganshin
Hello michael,

Tuesday, August 31, 2010, 9:27:17 PM, you wrote:

f :: Int -> Int

i.e. it's used when you define function types

> So it's a type constructor, not a type? Could you please provide a simple 
> example of its usage?

> Michael

> --- On Tue, 8/31/10, Vo Minh Thu  wrote:

> From: Vo Minh Thu 
> Subject: Re: [Haskell-cafe] On to applicative
> To: "michael rice" 
> Cc: haskell-cafe@haskell.org
> Date: Tuesday, August 31, 2010, 1:17 PM

> 2010/8/31 michael rice 
>>
>> "Learn You a Haskell ..."  says that (->) is a type just like Either. Where 
>> can I find its type definition?

> You can't define it *in* Haskell as user code. It is a  built-in infix
> type constructor (Either or Maybe are type constructors too, not just
> types). In fact, if you want to implement a simple, typed functional
> language, you'll find it is the only built-in type constructor you
> have to implement (as the implementor of the language).

> Also,
>   Show a => a
> is a type too, but you won't find a definition for 'a' or for '=>'.
> All those things are defined by the language.

> Cheers,
> Thu


>   


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Re: String vs ByteString

2010-08-17 Thread Bulat Ziganshin
Hello Tako,

Tuesday, August 17, 2010, 3:03:20 PM, you wrote:

> Unless a Char in Haskell is 32 bits (or at least more than 16 bits)
> it con NOT encode all Unicode points.

it's 32 bit


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Re: String vs ByteString

2010-08-17 Thread Bulat Ziganshin
Hello Tom,

Tuesday, August 17, 2010, 2:09:09 PM, you wrote:

> In the first iteration of the Text package, UTF-16 was chosen because
> it had a nice balance of arithmetic overhead and space.  The
> arithmetic for UTF-8 started to have serious performance impacts in
> situations where the entire document was outside ASCII (i.e. a Russian
> or Arabic document), but UTF-16 was still relatively compact

i don't understand what you mean. are you support all 2^20 codepoints
in Data.Text package?



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Embedded scripting Language for haskell app

2010-08-17 Thread Bulat Ziganshin
Hello Hemanth,

Tuesday, August 17, 2010, 2:05:44 PM, you wrote:

btw, i've written unfinished hslua tutorial:
http://haskell.org/haskellwiki/HsLua

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[4]: [Haskell-cafe] Re: String vs ByteString

2010-08-17 Thread Bulat Ziganshin
Hello Tako,

Tuesday, August 17, 2010, 12:46:35 PM, you wrote:

> not slower but require 2x more memory. speed is the same since
>  Unicode contains 2^20 codepoints

> This is not entirely correct because it all depends on your data.

of course i mean ascii chars

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[4]: [Haskell-cafe] Re: String vs ByteString

2010-08-17 Thread Bulat Ziganshin
Hello Johan,

Tuesday, August 17, 2010, 1:06:30 PM, you wrote:

> So it's not clear to me that using UTF-16 makes the program
> noticeably slower or use more memory on a real program.

it's clear misunderstanding. of course, not every program holds much
text data in memory. but some does, and here you will double memory
usage


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Re: String vs ByteString

2010-08-17 Thread Bulat Ziganshin
Hello Johan,

Tuesday, August 17, 2010, 12:20:37 PM, you wrote:

>  I agree, Data.Text is great.  Unfortunately, its internal use of UTF-16
>  makes it inefficient for many purposes.

> It's not clear to me that using UTF-16 internally does make
> Data.Text noticeably slower.

not slower but require 2x more memory. speed is the same since
Unicode contains 2^20 codepoints


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Bulat Ziganshin
Hello Daniel,

Sunday, August 15, 2010, 10:39:24 PM, you wrote:

> That's great. If that performance difference is a show stopper, one
> shouldn't go higher-level than C anyway :)

*all* speed measurements that find Haskell is as fast as C, was
broken. Let's see:

D:\testing>read MsOffice.arc
MsOffice.arc 317mb -- Done
Time 0.407021 seconds (timer accuracy 0.00 seconds)
Speed 779.505632 mbytes/sec


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Bulat Ziganshin
Hello Bryan,

Sunday, August 15, 2010, 10:04:01 PM, you wrote:

> shared on Friday, and boiled it down to a simple test case: how long does it 
> take to read a 31MB file?
> GNU wc -m:

there are even slower ways to do it if you need :)

if your data aren't cached, then speed is limited by HDD. if your data
are cached, it should be 20-50x faster. try cat >nul


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Re: philosophy of Haskell

2010-08-15 Thread Bulat Ziganshin
Hello Tillmann,

Sunday, August 15, 2010, 7:40:54 PM, you wrote:

> But in a world passing interpretation of IO, print is supposed to be a
> pure Haskell function. So the value world2 can only depend on the values
> of print and world1, but not on the actions of some concurrent thread.

the whole World includes any concurrent thread though ;)


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Unwrapping long lines in text files

2010-08-13 Thread Bulat Ziganshin
Hello michael,

Saturday, August 14, 2010, 5:38:46 AM, you wrote:

> The program below takes a text file and unwraps all lines to 72
> columns, but I'm getting an end of file message at the top of my output.

> How do I lose the EOF?

use isEOF function. even better, use interact


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Compiled OpenGL program has DOS window?

2010-08-13 Thread Bulat Ziganshin
Hello Henk-Jan,

Friday, August 13, 2010, 2:23:58 PM, you wrote:

> You can do this with the flag -optl-mwindows; this passes the flag
> -mwindows to the linker. Because this is a linker option, you cannot find
> it in the GHC documentation. This solution also works for other GUIs, like
> wxHaskell.

it may be added to some GHC FAQ though

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] What is <-

2010-08-08 Thread Bulat Ziganshin
Hello michael,

Sunday, August 8, 2010, 5:36:05 PM, you wrote:

i highly recommend you to read
http://sigfpe.blogspot.com/2006/08/you-could-have-invented-monads-and.html
that is the best introduction into monads i know

and then http://haskell.org/all_about_monads/html/index.html
- comprehensive tutorial about many useful monads

both are mentioned at 
http://en.wikipedia.org/wiki/Monad_%28functional_programming%29


> What is <- ? Couldn't find anything on Hoogle.

> 1)  main = do 
>   x <- getLine   -- get the value from the IO monad
>   putStrLn $ "You typed: " ++ x

> 2)  pythags = do
>   z <- [1..] --get the value from the List monad?
>   x <- [1..z]
>   y <- [x..z]
>   guard (x^2 + y^2 == z^2)
>   return (x, y, z)



> From: http://en.wikibooks.org/wiki/Haskell/Syntactic_sugar

> Do and proc notation


>   Sweet    Unsweet
> Monadic binding  do x <- getLIne  getLine >>= \x ->
>     putStrLn $ "You typed: " ++  x putStrLn $ "You typed: 
> " ++ x


> So, Example 2 desugared becomes...

>  [1..] >== \z ->  ?





> Michael


>   


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] trees and pointers

2010-07-16 Thread Bulat Ziganshin
Hello Jake,

Friday, July 16, 2010, 7:26:22 AM, you wrote:

> Excluding DiffArray under certain usage patterns of course, but
> DiffArray is slow for unknown reasons besides algorithmic complexity.

unknown reason = MVar usage

ArrayRef library contains parameterized DiffArray implementation that
may be specialized either to MVar or IORef usage


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Is my code too complicated?

2010-07-03 Thread Bulat Ziganshin
Hello Ertugrul,

Saturday, July 3, 2010, 4:25:22 PM, you wrote:

> This has proven very useful for me.  My usual way is writing monad
> transformers and sticking them together, often together with concurrent
> programming.

> ... /what/ my code is
> doing, because it's written in natural language as much as possible

can we see such code? i always thought that monad transformers are
hard to use since you need to lift operations from inner monads on every use

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Are you a Haskell expert? [How easy is it to hire Haskell programmers]

2010-07-03 Thread Bulat Ziganshin
Hello Ivan,

Saturday, July 3, 2010, 3:24:34 PM, you wrote:
>> haskell code is easily ported between OSes, unlike C one. when i
>> ported my application from Win to Linux, i spend one day on haskell
>> code and 3 days on C one, despite the fact that haskell code dealed
>> with OS interaction and C used purely for computations

> Care to provide more details?  This story intrigues me (even though I've
> never really used C that much, and would prefer to keep it that way).

since 2004 i'm developing FreeArc archiver, something like winzip. in
2007 i've ported it to Linux. the only Haskell part that required was
my own I/O library: i developed it in 2005 since ghc doesn't supported
large files and unicode filenames at that time. my library used
Win-specific calls and i, naturally, required to add some Unix way to
compile it - i just used standard Haskell I/O calls

generally speaking, as far as your program utilizes only existing
Haskell libraries, it just work. problems starts only when existing
Haskell libraries can't serve your needs and you start binding to some
C or OS-specific code

for the C part, i have found that some APIs i've used in mingw were in
fact MSVC-compatibility ones, and was absent in Linux gcc


i just looked at my darcs repository. Unix-specific patches were:

> added /dev/urandom as entropy source for Unix
> Unixifying: dir.size:=0
> Added Unix support for GetPhysicalMemory, GetProcessorsCount
> Unix: config files in "/etc"; fixed compilation scripts
> Unix: look for SFX in /usr/lib
> Unix: UTF8 for filelist/screen/filenames/cmdline encoding
> Unix: getThreadCPUTime
> CUI: hidden password input now works on Unix too

so, the main catch for C part were OS-specific calls like
GetPhysicalMemory - i spent lot of time reading mans. for Haskell
part, main changes were about default directories


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Are you a Haskell expert? [How easy is it to hire Haskell programmers]

2010-07-03 Thread Bulat Ziganshin
Hello Andrew,

Saturday, July 3, 2010, 1:57:22 PM, you wrote:

> (I suppose I'm just bitter because any Haskell libraries involving C are
> almost guaranteed to not work on Windows...)

haskell code is easily ported between OSes, unlike C one. when i
ported my application from Win to Linux, i spend one day on haskell
code and 3 days on C one, despite the fact that haskell code dealed
with OS interaction and C used purely for computations

C works on windows as well as it works on Unix, it just need some work
to be ported between OSes, and since most developers just use one OS,
C code has much more chances to remain OS-specific


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Core packages and locale support

2010-06-27 Thread Bulat Ziganshin
Hello Roman,

Sunday, June 27, 2010, 11:37:24 AM, you wrote:

>>> No! The target encoding is the current locale. It is a no-brainer to
>> not necessarily. current locale, encoding of current terminal and
>> encoding of every filesystem mounted are all different things
> And we should stick to the current locale. Problem solved.
> "6.3  CString
> The module CString provides routines marshalling Haskell into C strings
> and vice versa. The marshalling converts each Haskell character, 
> representing a Unicode code point, to one or more bytes in a manner 
> that, by default, is determined by the *current locale*."
> "The Haskell 98 Foreign Function Interface."

1. it doesn't work on practice. ghc provides simple 8-bit conversion
and i think a lot of code relies on this behavior

2. when you mount external/network volume, it doesn't necessarily has
the same encoding as your current locale



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Core packages and locale support

2010-06-27 Thread Bulat Ziganshin
Hello Roman,

Sunday, June 27, 2010, 11:28:49 AM, you wrote:
>>> Just do not change FilePath, what may be simpler?
>> if FilePath will become abstract type, it will break all programs
>> that use it since they use it as String
> Hello, do you read me? I said: "do not change FilePath".

what you mean by abstract type then? :)


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Core packages and locale support

2010-06-27 Thread Bulat Ziganshin
Hello Roman,

Sunday, June 27, 2010, 11:24:16 AM, you wrote:

> O'kay, but IMHO few people want to have a headache with recoding. You
> knew that the implementation was incorrect, why you relied on it?

what is alternative? :)  on windows i've used low-level open()-styly
APIs, on Linux i got the same results with official API



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Core packages and locale support

2010-06-27 Thread Bulat Ziganshin
Hello Roman,

Sunday, June 27, 2010, 11:11:59 AM, you wrote:

> No! The target encoding is the current locale. It is a no-brainer to

not necessarily. current locale, encoding of current terminal and
encoding of every filesystem mounted are all different things


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Core packages and locale support

2010-06-27 Thread Bulat Ziganshin
Hello Roman,

Sunday, June 27, 2010, 11:07:47 AM, you wrote:

>> Currently, FilePath is an alias for String.  Changing FilePath to a real
>> type
> Just do not change FilePath, what may be simpler?

if FilePath will become abstract type, it will break all programs
that use it since they use it as String



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Core packages and locale support

2010-06-26 Thread Bulat Ziganshin
Hello Roman,

Sunday, June 27, 2010, 3:52:54 AM, you wrote:

> I fail to see how it will brake programs. Current programs do not use
> Unicode because it is implemented incorrectly.

i use it. current Linux implementation treats String as sequence of
bytes, and with manual recoding it allows to use filesystems with
any encoding


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Core packages and locale support

2010-06-26 Thread Bulat Ziganshin
Hello Felipe,

Saturday, June 26, 2010, 4:54:16 PM, you wrote:

>> > Even if we said "we don't care", we at least should change
>> > FilePath to be [Word8], and not [String].  Currently filepaths

> other OSs worked fine, should I use this API (i.e. type FilePath
> = String) to its fullest extent, my program will suddently become
> unportable to all Unix OSs.

but what you propose cannot be used in Windows at all! while current
FilePath still works on Unix, with manual filenames en/decoding

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Core packages and locale support

2010-06-26 Thread Bulat Ziganshin
Hello Felipe,

Saturday, June 26, 2010, 4:44:20 PM, you wrote:

> Even if we said "we don't care", we at least should change
> FilePath to be [Word8], and not [String].  Currently filepaths
> are silently "truncated" if any codepoint is beyond 255.

and there is no OS except Unix ;)


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Type-Level Programming

2010-06-26 Thread Bulat Ziganshin
Hello Gábor,

Saturday, June 26, 2010, 4:29:28 PM, you wrote:

> It's interesting how C++ is imperative at the term level and
> functional at the type level

or logic? it supports indeterminate choice


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Network of GUI Controls - using MonadFix?

2010-06-24 Thread Bulat Ziganshin
Hello Felipe,

Thursday, June 24, 2010, 5:00:55 AM, you wrote:

>> Is that something that MonadFix is meant to be used for?

> In current Gtk libraries, no.  You'll do something like
> However, if some library required you to supply the action while
> constructing the button, then I guess the answer would be "yes".

he may have his own high-level abstractions that combine create and
connect, in this case the answer is yes:

rdo btn1 <- createAndConnectBtn btn2
btn2 <- createAndConnectBtn btn3
btn3 <- createAndConnectBtn btn1


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Huffman Codes in Haskell

2010-06-22 Thread Bulat Ziganshin
Hello ajb,

Wednesday, June 23, 2010, 6:58:30 AM, you wrote:

>  build ((w1,t1):(w2,t2):wts)
>= build $ insertBy (comparing fst) (w1+w2, Node t1 t2) wts

this algo is O(n^2). to be O(n) you should handle separate lists of
leafs and nodes, adding new nodes to the tail of second list


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Mapping a list of functions

2010-06-17 Thread Bulat Ziganshin
Hello Martin,

Thursday, June 17, 2010, 11:02:31 PM, you wrote:

> But what if I want to apply a list of functions to a single argument. I can

one more answer is "swing map":

http://www.haskell.org/haskellwiki/Pointfree#Swing



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Fun Facts: A lazy bill

2010-06-17 Thread Bulat Ziganshin
Hello Leonel,

Friday, June 18, 2010, 6:46:31 AM, you wrote:

> to be used. Look at the new 10.000 colones bill:

and this one - http://www.bccr.fi.cr/WebPages/PaginaInicio/NuevaFamilia/5.html
is for C++ programmers :)


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Terminology

2010-06-15 Thread Bulat Ziganshin
Hello Emmanuel,

Tuesday, June 15, 2010, 2:10:09 AM, you wrote:

> [f(a),f(b),f(c)] = g([a,b,c])

it looks a bit like vectorisation transformation in compilers


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[4]: [Haskell-cafe] Using the ContT monads for early exits of IO ?

2010-06-11 Thread Bulat Ziganshin
Hello Christopher,

Friday, June 11, 2010, 4:35:00 PM, you wrote:

> if xthen foo
> else if y then bar
> else if z then mu
> else zot

case () of
 _ | x -> foo
   | y -> bar
   | otherwise -> zor

it's usually considered as "haskell way" of doing this


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Using the ContT monads for early exits of IO ?

2010-06-11 Thread Bulat Ziganshin
Hello Christopher,

Friday, June 11, 2010, 4:06:05 PM, you wrote:

> do if x
>   then return ()
>   else do bar; continueComputation

i format it this way:

if x then return () else do
bar
continueComputation



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] is there a way to prove the equivalence of these two implementations of (Prelude) break function?

2010-06-08 Thread Bulat Ziganshin
Hello David,

Tuesday, June 8, 2010, 10:33:51 AM, you wrote:

>  ( my guess is USE_REPORT_PRELUDE compiles functions as defined in
> the haskell report, but the other version is faster and used by default. )

you are right


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[3]: [Haskell-cafe] Re: Unicode vs. System.Directory

2010-05-27 Thread Bulat Ziganshin
Hello Bulat,

Friday, May 28, 2010, 9:24:02 AM, you wrote:

>> I have finish all necessary GIO APIs at
>> http://patch-tag.com/r/AndyStewart/gio-branch/home

> but what is the license?

heh, i've found COPYING file. but what you mean? if it's just about
"one should share all improvements to the library he was made", it's
fine for me. but strictly speaking, LGPL also means "you should allow
user to replace himself GIO library with newer versions", it may be
both hard for me and useless for users


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Re: Unicode vs. System.Directory

2010-05-27 Thread Bulat Ziganshin
Hello Andy,

Friday, May 28, 2010, 1:05:59 AM, you wrote:

> Looks my file-manager:
> http://farm5.static.flickr.com/4027/4584389024_782b1e09ee_o.png

can you please share windows and linux executables and source code?

> I have finish all necessary GIO APIs at
> http://patch-tag.com/r/AndyStewart/gio-branch/home
> I will try to merge those APIs to next release version of gtk2hs when i
> have spare time.

it seems that i can just merge these sources into my program for a
while. but what is the license? believe it or not, but i have
commercial project on the march

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Re: Unicode vs. System.Directory

2010-05-27 Thread Bulat Ziganshin
Hello Andy,

Thursday, May 27, 2010, 5:45:27 PM, you wrote:

does it work both on linux and windows? i'm very interested to run
executables of both kinds and look what features are really supported
(i write file/archive manager and it seems that you have solved many
problems that drive me crazy, such as displaying icons/filetypes,
launching documents...)

> Hi Arie,

> If you don't mind binding code.
> You can try to use GIO APIs from my repository:
> http://patch-tag.com/r/AndyStewart/gio-branch/home

> GIO APIs handle unicode filename every well, and cross-platform.

> Cheers,

>   -- Andy

> Arie Peterson  writes:

>> After upgrading to haskell-platform-2010.1.0.0, with the improved unicode
>> support for IO in ghc-6.12, I hoped to be able to deal with filenames
>> containing non-ascii characters. This still seems problematic, though:
>>
>> $ ls
>> m?n??
>> $ ghci
>> GHCi, version 6.12.1: http://www.haskell.org/ghc/  :? for help
>> Prelude> :m +System.Directory 
>> Prelude System.Directory> getDirectoryContents "." >>= mapM_ putStrLn
>> ..
>> mAna?I±
>> .
>>
>> I hope this passes through the various email systems unharmed; on my
>> terminal, the output of 'ls' contains shiny unicode characters, while
>> 'ghci' garbles up the filename. (My locale is en_GB.utf8.)
>>
>> Similar problems arise with functions such as 'copyFile', which refuses to
>> handle filenames with non-ascii characters (unless wrapping it with
>> encoding functions).
>>
>>
>> Is this a known problem? I searched ghc's trac, but there are no relevant
>> bugs for the component 'libraries/directory'.
>>
>>
>> I have parts of a unicode-aware layer on top of System.Directory laying
>> around somewhere. I was rather hoping to ditch it, but I can polish it and
>> put it on hackage, if people are interested.
>>
>>
>> Kind regards,
>>
>> Arie

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


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] double2Float is faster than (fromRational . toRational)

2010-05-27 Thread Bulat Ziganshin
Hello Daniel,

Friday, May 21, 2010, 11:55:35 PM, you wrote:

> xf = (fromRational $ toRational xd) :: Float
> xf = double2Float xd

> am still surprised how often such kinds of unobvious problems occur
> while programming in Haskell

does it mean that all other languages you are used doesn't have such
problem or that you are an inexperienced programmer? :)


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] executeFile failing on macosx

2010-05-16 Thread Bulat Ziganshin
Hello David,

Sunday, May 16, 2010, 7:18:29 PM, you wrote:

> "executeFile" is failing for me on Mac OS X 10.5.8, with ghc 6.12.1
> when compiling with "-threaded".  Compiling without -threaded, or running on 
> linux is fine. 
>>  forkProcess $ executeFile "/bin/echo" False ["Ok"] Nothing

afair, forkProcess and -threaded shouldn't work together on any Unix.
can you try forkIO or forkOS instead?



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] [reactive] A pong and integrate

2010-05-15 Thread Bulat Ziganshin
Hello Limestraël,

Saturday, May 15, 2010, 7:02:38 PM, you wrote:

> But when I set my beat to tick every 60 times per second, the
> position is well updated, but I clearly see that the display 
> dramatically slows down after a few seconds of execution. Too heavy rate for 
> integrate?

it may be due to lot of uncollected garbage that is result of lazy
evaluation. profile program to check its GC times


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] What makes Haskell difficult as .NET?

2010-05-14 Thread Bulat Ziganshin
Hello Don,

Friday, May 14, 2010, 9:43:38 PM, you wrote:

> Most .NET libraries are imperative, use mutable state -- so binding to

they are also OOP. ocaml supports OOP while haskell doesn't


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] MultiParamTypeClasses, FunctionalDependencies and FlexibleInstances using GHCi

2010-05-14 Thread Bulat Ziganshin
Hello Julian,

Friday, May 14, 2010, 4:18:42 PM, you wrote:

> Now, if I type
>> 3 + 4
> it does not work, and i really don't understand why. If i ask GHCi
> for 3's type ($ :t 3) it will answer "3 :: (Prelude.Num t) => t".
> But, if 3 and 4 are Prelude.Nums and there is an instanfe Num x x x
> for x of Prelude.Num - than why can't GHC deduce from the
> definitions that 3 and 4, both Prelude.Nums, can be used with (+)
> since there is an instance for Prelude.Num and my class Num - and
> the result will of course be something of Prelude.Num?

because 3 and 4 may have different types. Num is a class, Int is a
concrete type. 3 without additional type signature is polymorphic
value. usually type inference deduce types of numeric constants (that
all are polymorphic) from context but in your case it's impossible

your functional dependency allows to fix result type once parameter
types are known, but not other way

you appeal to *instance* definition but haskell/ghc type inference
can't use instance heads to deduce types since classes are open and
anyone can add later code that breaks your assumption (imagine that
ghc generates code for your module and later this module is imported by
someone else and additional instances are provided)

btw, quite popular problem, it arrives here each month or so :)

there are some ghc pragmas that somewhat break this rule, you may try
allow-indecidable-insances or so. but it's dangerous way


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Re: Haskell and scripting

2010-05-05 Thread Bulat Ziganshin
Hello Ivan,

Wednesday, May 5, 2010, 4:43:48 PM, you wrote:
>> How do you embed Lua in Haskell?
> http://hackage.haskell.org/package/hslua

tutorial: http://haskell.org/haskellwiki/HsLua


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Haskell and scripting

2010-05-04 Thread Bulat Ziganshin
Hello minh,

Tuesday, May 4, 2010, 11:15:03 AM, you wrote:

> Numerous games include for instance a complete Lua interpreter,

that's just one 100 kb dll :)



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Writing C libraries in Haskell

2010-05-01 Thread Bulat Ziganshin
Hello Richard,

Saturday, May 1, 2010, 1:34:19 PM, you wrote:

> If libraries foo and bar are compiled using the same version of GHC, is
> is possible to link the two libraries into the same executable?  Does

at the last end, you can put each entire library plus ghc runtime into dll


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] are forkIO threads event-driven?

2010-04-29 Thread Bulat Ziganshin
Hello Aran,

Friday, April 30, 2010, 2:26:20 AM, you wrote:

> In GHC, if a thread spawned by forkIO blocks on some network or
> disk IO, is the threading system smart enough not to wake the thread

afaik, yes. it's controlled by special i/o thread that multiplexes all
i/o done via stdlibs. but ghc i/o manager can't use epoll/kqueue so
it's appropriate only for small (or medium?) servers

read "Writing High-Performance Server Applications in Haskell, Case
Study: A Haskell Web Server"
http://www.haskell.org/~simonmar/papers/web-server.ps.gz




-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Cabal package with BSD3 library and LGPL executable?

2010-04-29 Thread Bulat Ziganshin
Hello Stephen,

Thursday, April 29, 2010, 3:45:50 PM, you wrote:

license: custom or so. but future imaginary tools that automatically
checks license of entire library chain will fail


> Hello all

> How do I mark a Cabal package as containing a BSD3 library and an LGPL
> executable?

> I'm using CppHs (LGPL) from the exe but have no dependencies on it in
> the library; as the library might be independently useful I want it to
> be BSD3.

> As a caveat - I don't want two packages...

> Thanks

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


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Compressing GHC tarballs with LZMA

2010-04-24 Thread Bulat Ziganshin
Hello Leon,

Saturday, April 24, 2010, 12:23:58 AM, you wrote:

> file nearly a third smaller.   Given that many modern variants of the
> "tar" command support .tar.lzma files directly

isn't latest version of lzma-based compression use .xz extension?


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] GHC, odd concurrency space leak

2010-04-18 Thread Bulat Ziganshin
Hello Bertram,

Sunday, April 18, 2010, 3:36:31 AM, you wrote:

> This expands as

> always a = a >> always a
>  = a >> a >> always a
>  = a >> a >> a >> always a
> ...
> where each >> application is represented by a newly allocated object
> (or several, I have not looked at it in detail) on the heap.

why you think so? i always thought that >> in ghc just sequentially
executes statements, the RealWorld magic exists only at compile-time


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] GHC, odd concurrency space leak

2010-04-17 Thread Bulat Ziganshin
Hello Bertram,

Sunday, April 18, 2010, 12:11:05 AM, you wrote:

> always a = -- let act = a >> act in act
> do
> _ <- a
> always a
> 

> hinting at the real problem: 'always' actually creates a long chain of
> actions instead of tying the knot.

can you explain it deeper? it's what i see: always definition is
equivalent to

 always a = do a
   always a

what's the same as

 always a = a >> always a

that looks exactly like your commented out definition, except that it
doesn't create value act. but i don't see list of actions here




-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] GHC, odd concurrency space leak

2010-04-17 Thread Bulat Ziganshin
Hello Jason,

Saturday, April 17, 2010, 2:00:04 AM, you wrote:


> Well, I think Bulat correctly characterized the non-termination
> aspect.  I didn't think the cooperative aspect of threading applied
> with the threaded RTS, so I'm not 100% sure I believe his
> characterization, but otherwise it seems like a reasonable
> explanation. 

it's a well known side of ghc green threads implementation. read notes
in sources of Control.Concurrent module:

The concurrency extension for Haskell is described in the paper
/Concurrent Haskell/
.

Concurrency is "lightweight", which means that both thread creation
and context switching overheads are extremely low.  Scheduling of
Haskell threads is done internally in the Haskell runtime system, and
doesn't make use of any operating system-supplied thread packages.


  GHC implements pre-emptive multitasking: the execution of
  threads are interleaved in a random fashion.  More specifically,
  a thread may be pre-empted whenever it allocates some memory,
  which unfortunately means that tight loops which do no
  allocation tend to lock out other threads (this only seems to
  happen with pathological benchmark-style code, however).



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Floyd Warshall performance (again)

2010-04-16 Thread Bulat Ziganshin
Hello John,

Friday, April 16, 2010, 7:41:06 PM, you wrote:

>> sIZE = 1500

> and all references from "SIZE" to "sIZE", something ... changes.  A lot.

this one too? :D

let loop2 SIZE = return ()



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Floyd Warshall performance (again)

2010-04-16 Thread Bulat Ziganshin
Hello Mathieu,

Friday, April 16, 2010, 12:42:29 PM, you wrote:

> Sure. But I was curious if to see whether there was some optimization
> I had missed, seeing as other similarly low level programs, such as
> the nsieve benchmark of the language shootout, or the word counting
> program, manage to run within a few percentage points of C if not
> faster.

you know it's the big game with $0's hanging around. sometimes we
rewrite programs, sometimes libs and sometimes compiler itself. the
best way to optimize your program is to add it to shootout itself :)))

i know one case when required function was added to the library and i
know that ghc was added better code generation for short loops.
probably it was enough to shootout programs but not your one. but of
course if making full-fledged optimizing compiler was so easy, it was
made to C and Haskell many years ago

> Since this program doesn't use any features specific to
> functional programming, such as higher order functions, and mostly
> just calls out to imperative primitives of GHC not implemented in
> Haskell (such as unsafeRead and unsafeWrite), I would have thought
> that the gap in runtimes might have been smaller.

it's not runtimes, but code generation. ghc -O2 should be rather close to
gcc -O0. you just undervalue amount of work done in gcc in those 20
years :)


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Floyd Warshall performance (again)

2010-04-16 Thread Bulat Ziganshin
Hello Mathieu,

Friday, April 16, 2010, 12:06:06 PM, you wrote:

> actions and then running them using sequence_. But still this program
> runs 3 times slower than it's C counterpart:

ghc low-level code optimization cannot be compared with best modern C
compilers that's result of 20 years of optimization. ghc generates
machine code in rather simple idiomatic way, so it should be compared
to non-optimizing C compiler

another haskell compiler, jhc, generates idiomatic C code, that
therefore can be compiled by gcc to efficient machine code. but
overall jhc is pretty experimental compiler ATM


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] GHC, odd concurrency space leak

2010-04-15 Thread Bulat Ziganshin
Hello Neil,

Thursday, April 15, 2010, 12:37:35 PM, you wrote:

> I find non-termination with a much simpler program than yours (GHC 6.12.1):
>forkIO $ do putStrLn "Started thread"
>forever $ return ()

ghc multithreading is actually cooperative: it switches only on memory
allocation. since almost any haskell code allocates, there is no
problem - it works like preemptive one. but sometimes this assumption
fails - with optimization enabled, your code doesn't allocate so there
are no chances for thread switching. replacing return () with
threadDelay call solves the problem


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Can Haskell enforce the dimension?

2010-04-09 Thread Bulat Ziganshin
Hello Haihua,

Friday, April 9, 2010, 8:28:23 PM, you wrote:

> In C++, template can be used to enforce the dimension. For example,
> F=m*a is OK and F=m*t will issue a compile time error.

> Is there a way to do this in Haskell?

yes. but standard * operation has type t->t->t. so you need either to
use other operation or don't import standard Num class


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Metaprogramming in Haskell vs. Ocaml

2010-04-06 Thread Bulat Ziganshin
Hello aditya,

Saturday, April 3, 2010, 6:56:23 AM, you wrote:

> Haskell. And I'm also wondering why metaprogramming is used much more
> in Ocaml than in Haskell.

reasons are two-folded: haskell is more powerful language. in
particular, there are lots of generic programming approaches besides
TH. OTOH, TH is as powerful as any other syntax preprocessor, but not
as easy to use. especially if you try to learn it by reading original
papers

i suggest you to postpone learning TH. it's not Haskell way :)


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Space leak

2010-03-10 Thread Bulat Ziganshin
Hello Arnoldo,

Wednesday, March 10, 2010, 11:45:56 PM, you wrote:

> I am learning haskell and I found a space leak that I find
> difficult to solve. I've been asking at #haskell but we could not solve
> the issue.

what if you use program B on single file?


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Space leak

2010-03-10 Thread Bulat Ziganshin
Hello Arnoldo,

Wednesday, March 10, 2010, 11:45:56 PM, you wrote:

> I am learning haskell and I found a space leak that I find
> difficult to solve. I've been asking at #haskell but we could not solve
> the issue.

make some experiments - leave only one file and use version A, then
replace appendFile with writeFile

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Cabal dependency hell

2010-03-08 Thread Bulat Ziganshin
Hello Maciej,

Monday, March 8, 2010, 4:33:08 PM, you wrote:

> PS. I understand that content may be flame-gen. I am sorry in advance if
> such circumstances happen. However I believe that possible improvements
> in process are worth the risk.

i was the author of this idea and i thought that

1) package author should allow to use only versions of dependence that
he know will work

2) if new version of dependence arrives, package author should upload
minor update of his package that allows to use it



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] GPL answers from the SFLC (WAS: Re: ANN: hakyll-0.1)

2010-03-04 Thread Bulat Ziganshin
Hello Matthias,

Friday, March 5, 2010, 12:56:48 AM, you wrote:

>> [...] The SFLC holds that a
>> library that depends on a GPL'd library must in turn be GPL'd, even if
>> the library is only distributed as source and not in binary form.

> Was this a general statement

yes. it's soul of GPL idea, and it's why BG called GPL a virus :)


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Optimizing hash array mapped tries

2010-02-24 Thread Bulat Ziganshin
Hello Edward,

Wednesday, February 24, 2010, 10:32:59 PM, you wrote:

> I'd be really curious about techniques that permit mutation during
> the construction of functional datastructures; this seems like a cool
> way to get fast performance w/o giving up any of the benefits of
> immutability.  Unfortunately, my (admittedly short) experiments in
> this domain ran up against the difficulty that vector didn't let me
> unsafely freeze its mutable version. :-)

actually, this technique is already used in haskell. look into array
library sources, search for freeze


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Linux ghci vs Windows ghci

2010-02-24 Thread Bulat Ziganshin
Hello Brandon,

Wednesday, February 24, 2010, 8:08:41 AM, you wrote:

>> I feel that ghci code executing speed in guest os is 1.5~2x faster
>> than host os

> My guess is that GHC (and the GHC RTS) on win32 is using a POSIX  
> emulation layer supplied by mingw32 for all system calls, introducing
> extra overhead.

1. yes, mingw is using POSIX emulation layer for file operations, but
i don't believe that it provides any serious overhead - even for i/o

2. this example was purely computational, no OS calls involved




-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Threading and FFI

2010-02-17 Thread Bulat Ziganshin
Hello Yves,

Thursday, February 18, 2010, 2:10:42 AM, you wrote:

> Okay! So under UNIX, haskell threaded runtime uses pthreads, if I well
> understood.

not exactly. it still uses lightweight (green) threads, but starts
additional OS threads as required to keep N haskell threads running.
it's very smart


> To sum up, in order to achieve what I want, I have no other choice than
> compiling with '-threading' and importing as 'safe' the functions which can
> make a 'sleep'.

> Thanks!


> Ben Franksen wrote:
>> 
>> Yves Pares wrote:
>>> I've also discovered something interesting: when I link with the
>>> 'threaded' runtime, but let the program use only one core (with '+RTS
>>> -N1'), the problem disappears. How comes?
>>> The whole thing remains a mystery, because I think what I'm trying to do
>>> is quite common...
>>> 
>>> 
>>> Yves Pares wrote:
 
 There is a minimal code which produces this issue:
  http://old.nabble.com/file/p27613138/func.c func.c
  http://old.nabble.com/file/p27613138/main.hs main.hs
 
 
 Yves Pares wrote:
> 
> Well I tried both 'unsafe' and 'safe', and actually I saw no
> difference...
> Even with 'safe', I see a huge difference between calling a C function
> which sleeps and another which doesn't. When there is a sleep, the
> other
> thread is really slower (it just prints numbers, and I look at which
> pace they're displayed).
>> 
>> This is to be expected. From the docs
>> (http://www.haskell.org/ghc/docs/latest/html/libraries/base-4.2.0.0/Control-Concurrent.html#10):
>> 
>> "The downside of having lightweight threads is that only one can run at a
>> time, so if one thread blocks in a foreign call, for example, the other
>> threads cannot continue. The GHC runtime works around this by making use
>> of
>> full OS threads where necessary. When the program is built with
>> the -threaded option (to link against the multithreaded version of the
>> runtime), a thread making a safe foreign call will not block the other
>> threads in the system; another OS thread will take over running Haskell
>> threads until the original call returns. The runtime maintains a pool of
>> these worker threads so that multiple Haskell threads can be involved in
>> external calls simultaneously."
>> 
>> IIRC, with -threaded, the RTS spawns a separate OS thread for 'safe'
>> foreign
>> calls _in addition_ to the OS threads used for Haskell code (the number of
>> which you give with the +RTS -N option).
>> 
>> Cheers
>> Ben
>> 
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>> 
>> 


> -
> Yves Pares

> Live long and prosper



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] How many "Haskell Engineer I/II/III"s are there?

2010-02-10 Thread Bulat Ziganshin
Hello Jason,

Wednesday, February 10, 2010, 6:59:42 PM, you wrote:

>   I wonder how many people actually write Haskell,
>   principally or exclusively, at work?

i work on commercial program. once it will start selling, i will
publish here the story 

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Compiling on Windows - using a particular Manifest file

2010-02-09 Thread Bulat Ziganshin
Hello Günther,

Tuesday, February 9, 2010, 4:03:48 AM, you wrote:

> how can I make ghc use a particular manifest file for embedding? (on
> Windows)

compile.cmd:
windres.exe -I. Register.rc res.o
g++.exe Register.cpp res.o

Register.rc:
1   24  "Register.exe.manifest"


windres is standard mingw tool


alternatively:

mt.exe -manifest Register64.exe.manifest -outputresource:Register64.exe

where mt.exe is MSVS tool (probably available in free MSVS Express)


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] GUI programming

2010-02-08 Thread Bulat Ziganshin
Hello Felipe,

Monday, February 8, 2010, 1:10:07 PM, you wrote:

>> As I understand Gtk2hs still don't run in -threaded environment.

> It does run, just use unsafeInitGUIForThreadedRTS.

... and run all GUI primitives via special wrapper or in GUI thread

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] safe lazy IO or Iteratee?

2010-02-04 Thread Bulat Ziganshin
Hello John,

Thursday, February 4, 2010, 11:51:59 PM, you wrote:

> tl;dr: Lots of smart people, with a history of being right about this
> sort of thing, say iteratees are better. Evidence suggests
> iteratee-based IO is faster and more predictable than lazy IO.
> Iteratees are really hard to understand.

thank you! good time for iteratee tutorials? ;)


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Re: Nested Types stack size ...

2010-02-04 Thread Bulat Ziganshin
Hello Günther,

Thursday, February 4, 2010, 6:49:05 PM, you wrote:

> Can I set this in the source code itself too?

http://www.haskell.org/ghc/docs/latest/html/users_guide/flag-reference.html
says that this option is dynamic so afaik it should work


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[4]: [Haskell-cafe] UTF-16 to UTF-8

2010-01-28 Thread Bulat Ziganshin
Hello Johan,

Thursday, January 28, 2010, 4:20:48 PM, you wrote:

> Haskell String type isn't UTF-8 encoded. it's [Char] where Char is in
>  UCS-4 aka UTF-32 :)

> That's not quite correct. [Char] is a sequence of Unicode code
> points, UTF-32 is one possible encoding of those code points. The
> difference is similar to the one between an integer an e.g. its string 
> representation.

i say exactly about its encoding :D


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] UTF-16 to UTF-8

2010-01-28 Thread Bulat Ziganshin
Hello Gunther,

Thursday, January 28, 2010, 4:07:07 PM, you wrote:

> thanks for the tip, but how do I use the library?
> I can't really make out how to feed it UTF-16 and get String (UTF-8) back.

Haskell String type isn't UTF-8 encoded. it's [Char] where Char is in
UCS-4 aka UTF-32 :)

> BTW: I need this function because I'm using HDBC-ODBC with MS Access and
> in MS Access apparently every string is in UTF-16.

look at withTString and its friends:

http://hamaoka.org/ghc6/libraries/Win32/src/System-Win32-Types.html


> Am 28.01.10 12:47, schrieb Ivan Lazar Miljenovic:
>> Gunther Schmidt  writes:
>>
>>> is there a library which converts from utf-16 to utf-8?
>>>  
>> The text library can (you can also choose between big and little endian
>> UTF-16).
>>
>>
>>> Gunther
>>>
>>>
>>> ___
>>> 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



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[4]: [Haskell-cafe] Poor man's generic programming

2010-01-19 Thread Bulat Ziganshin
Hello Neil,

Tuesday, January 19, 2010, 10:15:15 PM, you wrote:

>> can you give a permission to translate 
>> http://community.haskell.org/~ndm/darcs/uniplate/uniplate.htm
>> to Russian for http://fprog.ru/ online functional programming journal?

> Yes, that sounds great. However, I'm currently not a particular fan of
> the manual in it's current state - it isn't that well written and some
> bits need expanding. How about I revamp it, then let you know? I can
> probably do it within the next few weeks.

it would be even better. i just finished reading your paper - tutorial
doesn't emphasize some details i've found there, in particular
restrictions of Uniplate and how these are particularly overcomed by
BiPlate. i.e. it may be derived from tutorial but wasn't obvious for
me before i've read the paper


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


  1   2   3   4   5   6   7   8   9   10   >