Re: [Haskell-cafe] Re: ANNOUNCE: iteratee-compress 0.1.1

2010-10-24 Thread Felipe Lessa
On Sun, Oct 24, 2010 at 9:59 PM, Maciej Piechotka uzytkown...@gmail.com wrote:
 Currently I thought only about bzip2/gzip. Probably .xz support would
 follow if any.

 LZO, as you said, is on GPL-2. While I have no problems with GPL-2 some
 potential users may (Haskell tend to be BSD3 community). Does anyone
 knows if conditional compilation solves problem? In my interpretation of
 GPL-2 yes but I'm not sure.

Conditional compilation is tricky for licensing purposes, I think.
But a 'iteratee-compress-lzo' or 'iteratee-compress-gpl' package would
definitely avoid such issues.

Cheers!

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


Re: [Haskell-cafe] Redy to release gtk2hs-0.12.0!

2010-10-23 Thread Felipe Lessa
Great!  What's new in 0.12.0?  I don't see a NEWS file and the ChangeLog is old.

Cheers! =)

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


Re: [Haskell-cafe] Static computation/inlining

2010-10-11 Thread Felipe Lessa
On Sun, Oct 10, 2010 at 10:51 PM, Alexander Solla a...@2piix.com wrote:
 Is there anyway to instruct GHC (and maybe other compilers) to compute these
 maps statically? Are GHC and the other compilers smart enough to do it
 automatically? Although the list isn't huge, I would still rather get rid of
 the O(2*n) operation of turning it into maps at run-time. (Especially since
 some later list encodings like these might be enormous) What should I be
 looking into?

You may use Template Haskell and forget about the 'Data.Map's entirely =).

I've attached a proof-of-concept code that turns

  list :: [(a,b)]
  list = [(x1,y1), (x2, y2), ..., (xn, yn)]

into two functions (you can choose the names)

  fromAtoB :: a - b
  fromAtoB x1 = y1
  fromAtoB x2 = y2
  ...
  fromAtoB xn = yn

  fromBtoA :: b - a
  fromBtoA y1 = x1
  ...
  fromBtoA yn = xn

but with the arguments tranformed to patterns.

Compiling a test module:

$ ghc -ddump-splices -c ModuleWithFunctions.hs
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
Loading package array-0.3.0.1 ... linking ... done.
Loading package containers-0.3.0.0 ... linking ... done.
Loading package pretty-1.0.1.1 ... linking ... done.
Loading package template-haskell ... linking ... done.
ModuleWithFunctions.hs:1:0:
ModuleWithFunctions.hs:1:0: Splicing declarations
bimap
  map_country_to_country_code
  map_country_code_to_country
  countries_and_iso_country_codes
  ==
ModuleWithFunctions.hs:8:2-98
map_country_to_country_code Afghanistan
  = ISOCountryCode AF AFG (NC 4)
map_country_to_country_code AlandIslands
  = ISOCountryCode AX ALA (NC 248)
map_country_to_country_code Albania = ISOCountryCode AL ALB (NC 8)
map_country_to_country_code Zimbabwe
  = ISOCountryCode ZW ZWE (NC 716)
map_country_code_to_country ISOCountryCode AF AFG NC 4
  = Afghanistan
map_country_code_to_country ISOCountryCode AX ALA NC 248
  = AlandIslands
map_country_code_to_country ISOCountryCode AL ALB NC 8 = Albania
map_country_code_to_country ISOCountryCode ZW ZWE NC 716 = Zimbabwe


So two functions were spliced into your code with explicit pattern
matches.  I don't know how efficient is the code that GHC generates
for functions with many patterns.  Now, testing them:

$ ghci
GHCi, version 6.12.3: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
:Prelude :l Module
[4 of 4] Compiling Module   ( Module.hs, interpreted )
Ok, modules loaded: Module, ModuleWithData, ModuleWithFunctions, Template.
*Module :bro Module
data Country = Afghanistan | AlandIslands | Albania | Zimbabwe
data ISOCountryCode = ISOCountryCode TwoCode ThreeCode NumCode
data NumCode = NC Int
data ThreeCode = AFG | ALA | ALB | ZWE
data TwoCode = AF | AX | AL | ZW
countries_and_iso_country_codes :: [(Country, ISOCountryCode)]
isoNumericCode :: Int - NumCode
map_country_code_to_country :: ISOCountryCode - Country
map_country_to_country_code :: Country - ISOCountryCode
*Module map_country_to_country_code Albania
Loading package array-0.3.0.1 ... linking ... done.
Loading package containers-0.3.0.0 ... linking ... done.
Loading package pretty-1.0.1.1 ... linking ... done.
Loading package template-haskell ... linking ... done.
ISOCountryCode AL ALB (NC 8)
*Module map_country_code_to_country $ ISOCountryCode AL ALB (NC 8)
Albania

Cheers! =)

-- 
Felipe.
{-# LANGUAGE DeriveDataTypeable #-}

module ModuleWithData where

import Data.Data
import Data.Typeable

data Country = Afghanistan | AlandIslands | Albania | Zimbabwe
   deriving (Data, Eq, Ord, Show, Typeable)

data ISOCountryCode = ISOCountryCode TwoCode ThreeCode NumCode
  deriving (Data, Eq, Ord, Show, Typeable)

data TwoCode = AF | AX | AL | ZW
   deriving (Data, Eq, Ord, Show, Typeable)

data ThreeCode = AFG | ALA | ALB | ZWE
 deriving (Data, Eq, Ord, Show, Typeable)

data NumCode = NC Int
   deriving (Data, Eq, Ord, Show, Typeable)

isoNumericCode :: Int - NumCode
isoNumericCode = NC

countries_and_iso_country_codes :: [ (Country, ISOCountryCode) ]
countries_and_iso_country_codes =
[ (Afghanistan,  ISOCountryCode AF AFG (isoNumericCode 004))
, (AlandIslands, ISOCountryCode AX ALA (isoNumericCode 248))
, (Albania,  ISOCountryCode AL ALB (isoNumericCode 008))
, (Zimbabwe, ISOCountryCode ZW ZWE (isoNumericCode 716))
]
{-# LANGUAGE TemplateHaskell #-}

module 

Re: [Haskell-cafe] Re: Re-order type (flip map)

2010-10-10 Thread Felipe Lessa
On Sun, Oct 10, 2010 at 6:32 PM, Johannes Waldmann
waldm...@imn.htwk-leipzig.de wrote:
 Oh, and while we're at it - are there standard notations
 for forward function composition and application?

 I mean instead of      h . g . f $ x
 I'd sometimes prefer   x ? f ? g ? h
 but what are the ?

import Control.Arrow

something = f  g  h $ x

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


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

2010-10-02 Thread Felipe Lessa
On Sat, Oct 2, 2010 at 4:13 PM, Christopher Done
chrisd...@googlemail.com wrote:
 There's nothing more annoying than having to introduce intermediate
 bindings when you're going to immediate pattern match against it
 immediately and never use it again. It's both annoying to have to
 think of a variable name that makes sense and is not in scope or will
 be in scope, and annoying to type it out, and it's just ugly. This is
 *not* a special-case, it happens all the time and it's one of the few
 things in the syntax I wish could be updated.

 I vote yes, yes, and double yes!

I wholly agree with Christopher and for the same reason, +1.

Thanks,

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


Re: [Haskell-cafe] ANN: contstuff: CPS-based monad transformers

2010-09-30 Thread Felipe Lessa
Very interesting!  And the API seems very nice, although I haven't
used the package.

Are there benchmarks for monad transformers?  How big is the
difference between CPS and non-CPS monad libraries?

Cheers!

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


Re: [Haskell-cafe] Inverse of HaskellDB

2010-09-30 Thread Felipe Lessa
On Wed, Sep 29, 2010 at 7:21 AM, Michael Snoyman mich...@snoyman.com wrote:
 I think this approach is not possible without involving some fairly
 ugly unsafeInterleaveIO/unsafePerformIO calls. A simple example using
 a common web programming example: support I have a multi-user blog
 site, where each user can have multiple entries. I would model this
 using standard Haskell datatypes as:

 data Entry = Entry { title :: String, content :: String }
 data Blogger = Blogger { name :: String, entries :: [Entry] }

 Obviously we'll need some kind of blogger loading function:

 getBloggerByName :: String - IO Blogger

 Either this will load up all entries (a potentially incredibly costly
 operation) or use unsafe IO down the road. Especially when using
 database connections, this can be incredibly bad: the connection could
 be closed, the SQL statement could be reused by another request, etc.

It may be possible to tag those data fields that are not to be
loaded on the spot.  For example,

 data Entry = Entry { title :: String, content :: String }
 data Blogger db = Blogger { name :: String, entries :: OnDB db [Entry] }

 class Monad db = Database db where
   data OnDB db :: * - *
   fetch :: OnDB db a - db a
   fetchSome :: Criteria a - OnDB db [a] - db [a]

 newtype InMemory a = InMemory a
 instance Database InMemory where
   newtype OnDB db a = OnDBMem a
   fetch (OnDBMem x) = return x
   fetchSome = ...

 instance Database SQL where
   ...

Cheers,

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


Re: [Haskell-cafe] Non-strict evaluation and concurrency (STM) : conflict?

2010-09-28 Thread Felipe Lessa
On Tue, Sep 28, 2010 at 10:06 AM, Romain Demeyer
romain.deme...@gmail.com wrote:
 Let's a function do_job, the function to execute by the threads (the
 workers) :
 do_job :: (b - a) - b - Inbox a - IO ()
 do_job f input inbox = do { value - return (f input)
                           ; atomically ( writeMsg inbox value ) }

First of all, note that

  do v - return (f x)
 ...

is exactly the same as

  do let v = f x
 ...

Now, if you want to evaluate your value to WHNF (Weak Head Normal
Formal), you may use

 do_job :: (b - a) - b - Inbox a - IO ()
 do_job f input inbox = do
   value - evaluate (f input)
   atomically (writeMsg inbox value)

This will work pretty well if your value is simple (eg. an Int)
but not so well if it is complex (eg. a Data.Map) because it will
evaluate only as much as 'seq'.

You may than use the 'deepseq' package:

 import Control.DeepSeq

 do_job :: NFData a = (b - a) - b - Inbox a - IO ()
 do_job f input inbox =
   let value = f input
   in value `deepseq` atomically (writeMsg inbox value)

This will fully evaluate the structure before calling 'writeMsg'.

 That's what we want, but what is the explanation of this behavior? STM is
 designed to be optimistic, not blocking. So, does it means that the value
 is evaluated at commit-time?
 Do you know some problems that are related or do you know some works that
 can be useful at this subject?

Those values are pure, so if you say

  writeMsg inbox (f x)

then internally a thunk is created referencing 'f' and 'x', and a
pointer to that thunk is atomically commited.  Just like the rest
of the program.

The value is not being evaluated by STM at all, as your STM functions
don't need the value.  In your program is evaluating when you print
the answer in the main thread, as printing requires the value of the
computation.  If you didn't print, nothing would be computed at all.
Lazy =).

HTH,

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


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

2010-09-28 Thread Felipe Lessa
On Tue, Sep 28, 2010 at 10:41 AM, Peter Robinson thaldy...@gmail.com wrote:
 readTVarIO :: TVar a - IO a

One needs to know if it is ok to wrap this IO action into an STM
action.  For example,

 data I a = I a

 looselyReadTVar :: TVar a - STM a
 looselyReadTVar tvar =
   let v = unsafePerformIO (I $ readTVarIO tvar)
   in case v of I x - return x

The 'case' is needed because otherwise the TVar would be read
only when its value was requested, and we want to keep the
ordering.  The 'I' datatype is used to avoid evaluating the
user's value (which could even be 'undefined').

Note that this function can be used on any monad, but I don't
think that is a good idea =).

Cheers!

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


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

2010-09-28 Thread Felipe Lessa
On Tue, Sep 28, 2010 at 11:01 AM, Antoine Latter aslat...@gmail.com wrote:
 Isn't there an 'unsafeIOToSTM' function somewhere? Something like:

 unsafeIOToSTM (IO k) = STM k

 Then you might not need the case statement.

I thought there was, but I couldn't find it in the 'stm' package [1],
using Hoogle [2] nor using Hayoo [3].

[1] http://hackage.haskell.org/package/stm
[2] http://haskell.org/hoogle/?hoogle=IO+a+-%3E+STM+a
[3] http://holumbus.fh-wedel.de/hayoo/hayoo.html#0:stmtoio

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


Re: [Haskell-cafe] Non-strict evaluation and concurrency (STM) : conflict?

2010-09-28 Thread Felipe Lessa
On Tue, Sep 28, 2010 at 11:38 AM, Romain Demeyer
romain.deme...@gmail.com wrote:
 Does it means that the value is computed by the caller, based on the
 thunk, and not by the worker itself?

It is computed by the one who needs the value.  Your worker doesn't.
Note that the value is computed on 'print', which is *after* the
worker has returned the value.  So, it is the caller who evaluates,
but it does not evaluate while calling the worker.

 In this case, in this specific example, it would mean that this program does
 not exploit the parallelism at all (except using deepseq or seq).
 I understand the principles (lazy evaluation, thunk,...) , but I'm surprised
 that no work has been done to solve this problem (in the sense that it's
 not intuitive to write concurrent programs in this context).

It is not a problem, it is a feature.  It is our beloved lazy
evaluation applied to STM.

Alas, there isn't a single solution.  You may want 'seq', 'deepseq'
or something between.  Your data may already be in WHNF or HNF, so
calling 'seq' or 'deepseq' always would decrease performance for no
gain on these cases.  And sometimes you really want the lazy
behaviour, for example, if you were using an infinite data structure.

It is only a problem when you are learning how to use concurrency or
parallelism in Haskell.  Just repeat to yourself that everything is
lazy and you'll get used to it =).

Cheers,

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


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-27 Thread Felipe Lessa
On Mon, Sep 27, 2010 at 6:28 PM, Gregory Collins
g...@gregorycollins.net wrote:
 Also, if you're reading code in a proportional font, you're doing
 it wrong.

You may have nice codes using proportional fonts using LaTeX package
'listings'.  Even in a proportional font it lines things up.  Note,
however, that you need to write *your* LaTeX source code in a
fixed-width font for 'listings' to understand where things should be
lined up.

Unfortunately we don't have this mode in any editor as far as I know.
And even if we did, I don't know how the same code would be viewed in
another editor.  Reading 'listings'-style LaTeX isn't funny, much less
writing.

Cheers! :)

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


Re: [Haskell-cafe] [PREANNOUNCE] Crypto-API Major Version Bump (0.1.0.0)

2010-09-15 Thread Felipe Lessa
On Wed, Sep 15, 2010 at 9:54 PM, Thomas DuBuisson
thomas.dubuis...@gmail.com wrote:
 * cereal = 0.2   0.3 (was == 0.2.*)

Do you mean, = 0.2   0.4?

Cheers! =)

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


Re: [Haskell-cafe] Data.Text performance problem

2010-09-12 Thread Felipe Lessa
On Sun, Sep 12, 2010 at 10:06 PM, Bryan O'Sullivan b...@serpentine.com wrote:
 text 0.8.1.0 is now up on hackage, with the fix included. Enjoy!

Wow! That was fast! =)

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


Re: [Haskell-cafe] gathering position information lazily using traverse

2010-09-10 Thread Felipe Lessa
H...

On Fri, Sep 10, 2010 at 6:47 PM, Jan Christiansen
j...@informatik.uni-kiel.de wrote:
  instance Applicative Proj where
    pure = Proj . const
    Proj f * Proj x = Proj (\p - f (False:p) (x (True:p)))

  (pure f) * Proj x
   === Proj (const f) * Proj x
   === Proj (\p - (const f) (False:p) (x (True:p)))
   === Proj (\p - f (x (True:p)))

  Proj f * (pure x)
   === Proj f * Proj (const x)
   === Proj (\p - f (False:p) ((const x) (True:p)))
   === Proj (\p - f (False:p) x))

  instance Applicative Proj where
    pure x = Pure x
    Pure f * Pure x = Pure (f x)
    Pure f * Proj x = Proj (\p - f (x p))
    Proj f * Pure x = Proj (\p - f p x)
    Proj f * Proj x = Proj (\p - f (False:p) (x (True:p)))

  (pure f) * Proj x
   === Pure f * Proj x
   === Proj (\p - f (x p))

  (Proj f) * (pure x)
   === Proj f * Pure x
   === Proj (\p - f p x)

Was this difference intended?

Cheers! =)

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


Re: [Haskell-cafe] Will GHC 6.14 with LLVM use LLVM C compiler to compile external C Libraries

2010-09-09 Thread Felipe Lessa
On Thu, Sep 9, 2010 at 9:08 PM, John Lask jvl...@hotmail.com wrote:
 so it seems that the gcc support infrastructure that is currently integrated
 into ghc will still be required. Then the question arises what library
 formats will ghc use under the circumstances ?(.bc, .a) and how will the two
 be integrated?

As far as I know, the same files are used.  See [1], for example.

[1] http://llvm.org/docs/GoldPlugin.html

Cheers!

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


Re: [Haskell-cafe] ANNOUNCE: Grempa 0.1.0, Embedded grammar DSL and LALR parser generator

2010-09-06 Thread Felipe Lessa
On Mon, Sep 6, 2010 at 2:45 PM, Olle Fredriksson
fredriksson.o...@gmail.com wrote:
     expr :: Grammar Char E
     expr = do
       rec
         e - rule [ Plus  @ e # '+' # t
                   , id    @ t
                   ]
         t - rule [ Times @ t # '*' # f
                   , id    @ f
                   ]
         f - rule [ id    @ '(' # e # ')'
                   , Var   @ 'x'
                   ]
       return e

Looks like Applicative style.  This is good, even while I don't really
know why we are seeing @ and # instead of $ and *.

How does Grempa compare with other parsing libraries/tools, such as
Parsec, Attoparsec and Happy, with regard to ease of use and
performance?

Cheers! =)

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


Re: [Haskell-cafe] Re: Hackage on Linux

2010-08-27 Thread Felipe Lessa
On 8/27/10, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:
 Admittedly, Haskell has no multi-line
 String support which would make defining something like the
 Description field harder...

Quick correction: Haskell *does* have multi-line strings. For example:

This is a\
\ nice string

Note, however, that CPP doesn't like them.

Cheers! =)

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


Re: [Haskell-cafe] Re: [Haskell] Re: ANNOUNCE: enumerator, an alternative iteratee package

2010-08-23 Thread Felipe Lessa
Hello, Simon!

On Mon, Aug 23, 2010 at 8:00 AM, Simon Marlow marlo...@gmail.com wrote:
 The issue is that hGet always waits for a complete buffer-full of data
 before returning.  The hWaitForInput/hGetNonBlocking combination fixes that
 problem, but you have to be careful to make sure that the Handle is in
 binary mode, otherwise hWaitForInput will not behave the way you expect (it
 will decode the input byte stream, and wait for a full character).  For more
 information, see

 http://hackage.haskell.org/trac/ghc/ticket/3808

 A better fix is to use hGetBufSome, but (a) it is only available in GHC 6.14
 which isn't released yet, and (b) there isn't a bytestring wrapper for it
 yet.

So there really is a problem in the documentation of hGetBuf.  I
assume it got fixed in HEAD together with hGetBufSome.

Cheers! =)

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


Re: [Haskell-cafe] Re: [Haskell] Re: ANNOUNCE: enumerator, an alternative iteratee package

2010-08-23 Thread Felipe Lessa
On Mon, Aug 23, 2010 at 8:29 AM, Simon Marlow marlo...@gmail.com wrote:
 Which documentation are you referring to?  This looks ok to me:

 http://www.haskell.org/ghc/docs/6.12.2/html/libraries/base-4.2.0.1/System-IO.html#v%3AhGetBuf

Indeed, while there isn't a big fat warning, it does say that it reads
'count' bytes.

However, both RawIO.read and BufferedIO.fillReadBuffer are a bit
misleading.  The former says that it doesn't block when there isn't
data available, the latter doesn't say anything.

http://hackage.haskell.org/packages/archive/base/4.2.0.1/doc/html/src/GHC-IO-Device.html#RawIO
http://hackage.haskell.org/packages/archive/base/4.2.0.1/doc/html/src/GHC-IO-BufferedIO.html#BufferedIO

Cheers! =)

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


Re: [Haskell-cafe] Re: [Haskell] Re: ANNOUNCE: enumerator, an alternative iteratee package

2010-08-23 Thread Felipe Lessa
On Mon, Aug 23, 2010 at 8:51 AM, Simon Marlow marlo...@gmail.com wrote:
 Hmm, RawIO.read looks ok:

 -- | Read up to the specified number of bytes, returning the number
 -- of bytes actually read.  This function should only block if there
 -- is no data available.  If there is not enough data available,
 -- then the function should just return the available data. A return
 -- value of zero indicates that the end of the data stream (e.g. end
 -- of file) has been reached.

 that seems pretty clear to me.  No?

It says that it should only block if there is no data available.  I
assumed that fillReadBuffer has the same semantics.  If both do not
block if there is data, then hGetBuf would not wait for the buffer to
be filled, if I am reading its source correctly [1].  Either they do
block until the buffer is filled, or I'm misreading hGetBuf/bufRead.
=)

[1] 
http://www.haskell.org/ghc/docs/6.12.2/html/libraries/base-4.2.0.1/src/GHC-IO-Handle-Text.html#line-820

Cheers! =)

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


Re: [Haskell-cafe] Re: [Haskell] Re: ANNOUNCE: enumerator, an alternative iteratee package

2010-08-23 Thread Felipe Lessa
On Mon, Aug 23, 2010 at 9:00 AM, Simon Marlow marlo...@gmail.com wrote:
 I think it's the latter.  bufRead loops until it has read the full amount of
 data requested, or EOF is reached.

Hmmm... sorry about the noise then =).

Cheers,

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


Re: [Haskell-cafe] Unix emulation

2010-08-22 Thread Felipe Lessa
Hello!

I take it that the problem is that libcurl is a C library with a
Unix-like build system, and that is the problem that needs Cygwin,
right?

I'm not a Windows expert, but having C code is perfectly fine, I
guess.  My 'hipmunk' library includes a whole C library.  When I tried
to 'cabal install' it on Windows, it worked flawlessly even if I never
really did develop it for Windows.

Given that the problem is building libcurl, and not the Haskell curl
package, won't a binary distribution of libcurl cut it?  I was
thinking of [1], where there is an installer for libcurl.

http://curl.haxx.se/download.html#Win32

Cheers! =)

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


Re: [Haskell-cafe] GADT and problems with rigid type variables

2010-08-22 Thread Felipe Lessa
On Sun, Aug 22, 2010 at 7:47 PM, Daniel Peebles pumpkin...@gmail.com wrote:
 You could also do some (in my opinion) fairly nasty stuff with
 Dynamic or Typeable, adding a constraint to the Eq and
 attempting to cast at runtime (returning False if the cast
 returns Nothing).

This is what he's talking about:

 {-# LANGUAGE GADTs #-}

 import Data.Typeable (Typeable, cast)

 data Foo where
  Foo :: (Typeable t, Eq t) = t - Foo

 instance Eq Foo where
  (Foo a) == (Foo b) = maybe False (== b) (cast a)

Cheers,

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


Re: [Haskell] Re: [Haskell-cafe] ANNOUNCE: enumerator, an alternative iteratee package

2010-08-21 Thread Felipe Lessa
On Sat, Aug 21, 2010 at 5:40 AM, Magnus Therning mag...@therning.org wrote:
 It changes the timing.  The iteratee will receive the data sooner (when it's
 available rather than when the buffer is full).  This means it can fail
 *sooner*, in wall-clock time.

I still fail to see how this works.  So I went to see the sources.

In [1] we can see how hGet and hGetNonBlocking are defined.  The only
difference is that the former uses hGetBuf, and the latter uses
hGetBufNonBlocking.

[1] 
http://hackage.haskell.org/packages/archive/bytestring/0.9.1.7/doc/html/src/Data-ByteString.html#line-1908

hGetBuf's main loop is bufRead [2], while hGetBufNonBlocking's main
loop is bufReadNonBlocking [3].  Both are very similar.  The main
differences are RawIO.read vs RawIO.readNonBlocking [4], and
Buffered.fillReadBuffer vs Buffered.fillReadBuffer0 [5].  Reading
RawIO's documentation [4], we see that RawIO.read blocks only if there
is no data available.  So it doesn't wait for the buffer to be fully
filled, it just returns the available data.  Unfortunately,
BufferedIO's documentation [5] doesn't specify if
Buffered.fillReadBuffer should return the available data without
blocking.  However, it does specify that that it should be blocking
if the are no bytes available.

[2] 
http://hackage.haskell.org/packages/archive/base/4.2.0.1/doc/html/src/GHC-IO-Handle-Text.html#line-820
[3] 
http://hackage.haskell.org/packages/archive/base/4.2.0.1/doc/html/src/GHC-IO-Handle-Text.html#bufReadNonBlocking
[4] 
http://hackage.haskell.org/packages/archive/base/4.2.0.1/doc/html/src/GHC-IO-Device.html#RawIO
[5] 
http://hackage.haskell.org/packages/archive/base/4.2.0.1/doc/html/src/GHC-IO-BufferedIO.html#BufferedIO

So, assuming that the semantics of BufferedIO are the same as RawIO's,
*both* are non-blocking whenever data is already available.  None of
them wait until the buffer is full.  The difference lies in whether
they block if there is no data available.  However, when there isn't
data the enumarator *always* wants to block.  So using non-blocking IO
doesn't give anything, only complicates the code.

Am I misreading the docs/source somewhere?  =)

Cheers!

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


Re: [Haskell-cafe] lazy skip list?

2010-08-20 Thread Felipe Lessa
On Fri, Aug 20, 2010 at 3:57 AM, Luke Palmer lrpal...@gmail.com wrote:
 On Thu, Aug 19, 2010 at 9:57 PM, Felipe Lessa felipe.le...@gmail.com wrote:
 However, I haven't thought about how operations such as 'cons' and
 'tail' would be implemented =).  OP just asked about indexing ;-).

 Well if all you need is indexing, then an integer trie does it, right?
  http://hackage.haskell.org/package/data-inttrie

Probably!  More specifically,

newtype SkipList a = (Int, IntTrie a)

index :: SkipList a - Int - Maybe a
index i (n, t) = if i  n  i = 0 then Just (apply t i) else Nothing

However, with the API exposed in data-inttrie it isn't posssible to
implement fromList/toList in time O(n), only O(n log n), assuming that
modify/apply are O(log n).  Worse yet, if we wanted our fromList to
work with infinite lists we would need to do something like

import Data.List (genericLength)
import Number.Peano.Inf (Nat) -- from peano-inf on Hackage

newtype SkipList a = (Nat, IntTrie a)

fromList :: [a] - SkipList a
fromList xs = (genericLength xs, fmap (xs !!) identity)

The problem here is that 'fromList' is now O(n²).  If IntTrie exposed
an Traversable interface, I think it would be possible to write a
'fromList' in O(n) using a state monad.  However, I don't know if it
is possible to write a Traversable interface in the first place.

Cheers! =)

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


Re: [Haskell] Re: [Haskell-cafe] ANNOUNCE: enumerator, an alternative iteratee package

2010-08-20 Thread Felipe Lessa
On Fri, Aug 20, 2010 at 12:51 PM, John Millikin jmilli...@gmail.com wrote:
 Currently, I'm planning on the following type signatures for D.E.Text.
 'enumHandle' will use Text's hGetLine, since there doesn't seem to be
 any text-based equivalent to ByteString's 'hGet'.

CC'ing text's maintainer.  Using 'hGetLine' will cause baaad surprises
when you process a 10 GiB file with no '\n' in sight.

Cheers! =)

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


Re: [Haskell] Re: [Haskell-cafe] ANNOUNCE: enumerator, an alternative iteratee package

2010-08-20 Thread Felipe Lessa
On Fri, Aug 20, 2010 at 1:12 PM, John Millikin jmilli...@gmail.com wrote:
 This thought occurred to me, but really, how often are you going to
 have a 10 GiB **text** file with no newlines? Remember, this is for
 text (log files, INI-style configs, plain .txt), not binary (HTML,
 XML, JSON). Off the top of my head, I can't think of any case where
 you'd expect to see 10 GiB in a single line.

 In the worst case, you can just use decode to process bytes coming
 from the ByteString-based enumHandle, which should give nicely chunked
 text.

I was thinking about an attacker, not a use case.  Think of a web
server accepting queries using iteratees internally.  This may open
door to at least DoS attacks.

And then, we use iteratees because we don't like the unpredictability
of lazy IO.  Why should iteratees be unpredictable when dealing with
Text?  Besides the memory consumption problem, there may be
performance problems if the lines are too short.

Cheers! =)

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


Re: [Haskell-cafe] Re: ANNOUNCE: enumerator, an alternative iteratee package

2010-08-20 Thread Felipe Lessa
On Sat, Aug 21, 2010 at 12:30 AM, John Millikin jmilli...@gmail.com wrote:
 Just released 0.2. It has the text IO and codecs module, with support
 for ASCII, ISO-8859-1, UTF-8, UTF-16, and UTF-32. It should be
 relatively easy to add support for codec libraries like libicu or
 libiconv in the future. Both encoding and decoding are incremental, so
 you can (for example) process million-line logfiles in constant space.

I think it would be nice to say in the docs that a constant sized
buffer isn't used.

Alas, Data.Text.IO.hGetLine internally uses Data.Text.concat.  This
means that you need to do an additional copy whenever a newline is not
found in the first buffer.  So there's a performance reason to have an
hGet as well =).

 This also changes the binary enumHandle to use non-blocking IO, as
 recommended by Magnus Therning. I'm embarrassed to admit I still don't
 understand the improvement, exactly, but three people so far have told
 me it's a good idea.

Me neither =).

Cheers!

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


Re: [Haskell-cafe] lazy skip list?

2010-08-19 Thread Felipe Lessa
H


{-# LANGUAGE GADTs, EmptyDataDecls, KindSignatures #-}

data Z :: *
data S :: * - *

--

data SkipList s a where
Empty :: SkipList s a
Cons  :: Element (S s) a - SkipList (S s) a - SkipList s a

instance Show a = Show (SkipList s a) where
showsPrec d Empty =
showString Empty
showsPrec d (Cons elm xs) =
showParen (d  10) $
showString Cons  .
showsPrec 11 elm . (' ':) .
showsPrec 11 xs

--

data Element s a where
None   :: Element s a
Branch :: !Int - a - Element s a - Element s a - Element (S s) a

instance Show a = Show (Element s a) where
showsPrec d None =
showString None
showsPrec d (Branch sz x l r) =
showParen (d  10) $
showString Branch  .
showsPrec 11 sz . (' ':) .
showsPrec 11 x  . (' ':) .
showsPrec 11 l  . (' ':) .
showsPrec 11 r

sizeE :: Element s a - Int
sizeE None = 0
sizeE (Branch n _ _ _) = n

branch :: a - Element s a - Element s a - Element (S s) a
branch x l r = Branch (sizeE l + sizeE r + 1) x l r

--

fromList :: ElementFromList s = [a] - SkipList s a
fromList [] = Empty
fromList xs = let (elm, xs') = elementFromList xs
  in Cons elm (fromList xs')

class ElementFromList s where
elementFromList :: [a] - (Element s a, [a])

instance ElementFromList Z where
elementFromList xs = (None, xs)

instance ElementFromList s = ElementFromList (S s) where
elementFromList [] = (None, [])
elementFromList (x:xs) =
let (elmL, xsL) = elementFromList xs
(elmR, xsR) = elementFromList xsL
in (branch x elmL elmR, xsR)

--

toList :: SkipList s a - [a]
toList Empty = []
toList (Cons elm xs) = go elm (toList xs)
where
  go :: Element s a - [a] - [a]
  go None rest = rest
  go (Branch _ x l r) rest = x : go l (go r rest)

--

class Nth s where
nth :: Element s a - Int - Either Int a

instance Nth Z where
nth None i = Left i

instance Nth s = Nth (S s) where
nth None i = Left i
nth (Branch n x l r) i | i == 0= Right x
   | i = n= Left (i-n)
   | otherwise = either (nth r) Right $ nth l (i-1)

index :: Nth s = SkipList s a - Int - Maybe a
index Empty _ = Nothing
index (Cons elm xs) i = either (index xs) Just $ nth elm i


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


Re: [Haskell-cafe] lazy skip list?

2010-08-19 Thread Felipe Lessa
Oh, an example:

*Main fromList [1..8] :: SkipList Z Int
Cons (Branch 1 1 None None) (Cons (Branch 3 2 (Branch 1 3 None None)
(Branch 1 4 None None)) (Cons (Branch 4 5 (Branch 3 6 (Branch 1 7 None
None) (Branch 1 8 None None)) None) Empty))
*Main fromList [1..8] :: SkipList (S Z) Int
Cons (Branch 3 1 (Branch 1 2 None None) (Branch 1 3 None None)) (Cons
(Branch 5 4 (Branch 3 5 (Branch 1 6 None None) (Branch 1 7 None None))
(Branch 1 8 None None)) Empty)
*Main fromList [1..8] :: SkipList (S (S Z)) Int
Cons (Branch 7 1 (Branch 3 2 (Branch 1 3 None None) (Branch 1 4 None
None)) (Branch 3 5 (Branch 1 6 None None) (Branch 1 7 None None)))
(Cons (Branch 1 8 None None) Empty)

*Main let x = fromList [1..8] :: SkipList Z Int
*Main toList x
[1,2,3,4,5,6,7,8]
*Main x `index` 3
Just 4
*Main x `index` 8
Nothing

Cheers! =)

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


Re: [Haskell-cafe] lazy skip list?

2010-08-19 Thread Felipe Lessa
On Fri, Aug 20, 2010 at 12:57 AM, Felipe Lessa felipe.le...@gmail.com wrote:
 Alas, the idea is simple.  Each 'Element' contains up to 2^(s-1) data.
  For example, with an 'Element Z a' you can't store anything.  With an
 'Element (S Z) a' you may store zero or one datum.  With an 'Element
 (S (S Z)) a', you may store between 0 and 4 data, and so forth.

Erm, correcting myself:

Alas, the idea is simple.  Each 'Element' contains up to (2^s)-1 data.
 For example, with an 'Element Z a' you can't store anything.  With an
'Element (S Z) a' you may store zero or one datum.  With an 'Element
(S (S Z)) a', you may store between 0 and 3 data.  With an 'Element (S
(S (S Z))) a', you may store between 0 and 7 data, and so forth.

Cheers! =)

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


Re: [Haskell-cafe] lazy skip list?

2010-08-19 Thread Felipe Lessa
On Fri, Aug 20, 2010 at 12:49 AM, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:
 How about fromList [1..] like Evan's original email had (which I think
 is going to be a problem here as well)?

The only problem is that the Element's sizes will be forced up to
the point you need, but not anymore.

*Main (fromList [1..] :: SkipList Z Int) `index` 100
Just 101

Probably this small problem could be removed if the code was polished.

Alas, the idea is simple.  Each 'Element' contains up to 2^(s-1) data.
 For example, with an 'Element Z a' you can't store anything.  With an
'Element (S Z) a' you may store zero or one datum.  With an 'Element
(S (S Z)) a', you may store between 0 and 4 data, and so forth.

Then we just create an SkipList so that the Elements have an
increasing capacity.  When you 'Cons', the 'Element' of tail of the
SkipList will have twice more capacity than the 'Element' of the head.

However, I haven't thought about how operations such as 'cons' and
'tail' would be implemented =).  OP just asked about indexing ;-).

Cheers! =D

-- 
Felipe.
___
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-18 Thread Felipe Lessa
On Wed, Aug 18, 2010 at 4:42 AM, John Lask jvl...@hotmail.com wrote:
 On 18/08/2010 12:20 PM, Stephen Sinclair wrote:

 you could script in haskell by embedding hugs. Hugs exe + base lib ~ 1MB.


Hmmm... Would it be possible to pass complex values between the
program (with GHC) and the script (with Hugs)?  Probably there would
need to be done some serialization/deserialization, because GHC and
Hugs use different memory representations.  So you lose the ability to
transparently use script functions in you program, because some values
can't be serialized (e.g. infinite data structures, functions...) and
others are too costly and would double the memory requirements.

On the other hand, you may want use Hugs as Lua is used, creating
bindings in the Hugs/Lua world that can be used to call back to the
GHC world.  But if you go through this route, then perhaps using Lua
in the first place would be better.  It depends on how easy it is to
create these bindings in an embedded Hugs.

Cheers! =)

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


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

2010-08-17 Thread Felipe Lessa
Hello, Ketil Malde!

On Tue, Aug 17, 2010 at 8:02 AM, Ketil Malde ke...@malde.org wrote:
 Ivan Lazar Miljenovic ivan.miljeno...@gmail.com writes:

 Seeing as how the genome just uses 4 base letters,

 Yes, the bulk of the data is not really text at all, but each sequence
 (it's fragmented due to the molecular division into chromosomes, and
 due to incompleteness) also has a textual header.  Generally, the Fasta
 format looks like this:

  sequence-id some arbitrary metadata blah blah
  ACGATATACGCGCATGCGAT...
  ..lines and lines of letters...

 (As an aside, although there are only four nucleotides (ACGT), there are
 occasional wildcard characters, the most common being N for aNy
 nucleotide, but there are defined wildcards for all subsets of the alphabet.)

As someone who knows and uses your bio package, I'm almost
certain that Text really isn't the right data type for
representing everything.  Certainly *not* for the genomic data
itself.  In fact, a representation using 4 bits per base (4
nucleotides plus 12 other characters, such as gaps as aNy) is
easy to represent using ByteStrings with two bases per byte and
should halve the space requirements.

However, the header of each sequence is text, in the sense of
human language text, and ideally should be represented using
Text.  In other words, the sequence data type[1] currently is
defined as:

  type SeqData = Data.ByteString.Lazy.ByteString
  type QualData = Data.ByteString.Lazy.ByteString
  data Sequence t = Seq !SeqData !SeqData !(Maybe QualData)

[1] 
http://hackage.haskell.org/packages/archive/bio/0.4.6/doc/html/Bio-Sequence-SeqData.html#t:Sequence

where the meaning is that in 'Seq header seqdata qualdata',
'header' would be something like sequence-id some arbitrary
metadata blah blah and 'seqdata' would be ACGATATACGCGCATGCGAT.

But perhaps we should really have:

  type SeqData = Data.ByteString.Lazy.ByteString
  type QualData = Data.ByteString.Lazy.ByteString
  type HeaderData = Data.Text.Text -- strict is prolly a good choice here
  data Sequence t = Seq !HeaderData !SeqData !(Maybe QualData)

Semantically, this is the right choice, putting Text where there
is text.  We can read everything with ByteStrings and then use[2]

  decodeUtf8 :: ByteString - Text

[2] 
http://hackage.haskell.org/packages/archive/text/0.7.2.1/doc/html/Data-Text-Encoding.html#v:decodeUtf8

only for the header bits.  There is only one problem in this
approach, UTF-8 for the input FASTA file would be hardcoded.
Considering that probably nobody will be using UTF-16 or UTF-32
for the whole FASTA file, there remains only UTF-8 (from which
ASCII is just a special case) and other 8-bits encondings (such
as ISO8859-1, Shift-JIS, etc.).  I haven't seen a FASTA file with
characters outside the ASCII range yet, but I guess the choice of
UTF-8 shouldn't be a big problem.


 wouldn't it be better to not treat it as text but use something else?

 I generally use ByteStrings, with the .Char8 interface if/when
 appropriate.  This is actually a pretty good choice; even if people use
 Unicode in the headers, I don't particularly want to care - as long as
 it is transparent.  In some cases, I'd like to, say, search headers for
 some specific string - in these cases, a nice, tidy, rich, and optimized
 Data.ByteString(.Lazy).UTF8 would be nice.  (But obviously not terribly
 essential at the moment, since I haven't bothered to test the available
 options.  I guess for my stuff, the (human consumable) text bits are
 neither very performance intensive, nor large, so I could probably and
 fairly cheaply wrap relevant operations or fields with Data.Text's
 {de,en}codeUtf8.  And in practice - partly due to lacking software
 support, I'm sure - it's all ASCII anyway. :-)

Oh, so I didn't read this paragraph closely enough :).  In this
e-mail I'm basically agreeing with your thoughts here =).

And what do you think about creating a real SeqData data type
with two bases per byte?  In terms of processing speed I guess
there will be a small penalty, but if you need to have large
quantities of base pairs in memory this would double your
capacity =).

Cheers,

--
Felipe.
___
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 Felipe Lessa
On Tue, Aug 17, 2010 at 8:50 AM, Wouter Swierstra
wou...@vectorfabrics.com wrote:
 Can some one please give me a suggestion on the best choice for an
 embedded
 scripting Language for a haskell application?

 Why not use Haskell itself? I agree that C and Java aren't perhaps the
 best choice for application scripting – but both Xmonad and Yi have
 had quite some success using Haskell to script/configure a Haskell
 application.

First of all, size.  AFAIK, hint requires the full GHC to be
installed, which means that to distribute your program you need to
distribute at least a dozen mebibytes more.

And perhaps more importantly, sandboxing.  Reading hint's
documentation it isn't clear to me how one could have a whitelist of
packages and/or modules.  With Lua this is a no-brainer.

But I also think that Haskell makes a great scripting language.  I
guess its suitability depends on what kind of scripting you want to
do.

Cheers!

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


Re: [Haskell-cafe] Maintainer wanted for pappy

2010-08-17 Thread Felipe Lessa
On Tue, Aug 17, 2010 at 5:38 PM, Christopher Done
chrisd...@googlemail.com wrote:
 1. Interested in and will continue maintaining:
 gd, higherorder, cgi-utils, fastcgi, ircbouncer

Just out of curiosity, why do you use gd instead of cairo?

Cheers! =)

-- 
Felipe.
___
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 Felipe Lessa
On Tue, Aug 17, 2010 at 7:07 PM, Christopher Done
chrisd...@googlemail.com wrote:
 Sadly this is true. I went ahead and tested this to confirm; compiled
 mueval (which uses hint), copied the executable to a virtual machine
 and it required the GHC package repo among other GHC-related
 libraries.

 The size is indeed a problem. But how much? How does this compare to Lua et 
 al?

IIRC, the Haskell Platform installer for Windows has around 70 MiB.
So, if you want a simple installer to include in your installer, be
prepared to have another 70 MiB.  I said a dozen mebibytes (12 MiB)
because I think the bare minimum needs to have at least this size to
have something useful for an app, but this isn't backed up by
anything.

Lua, on the other hand, is embedded in the executable and weights less
than 200 KiB, probably much less than a typical Haskell executable.  I
don't know about other interpreters.



I just did a quick look at some executables I had in hand (compiled by
GHC 6.12.3) and the smallest one weights at 2.3 MiB.

Hmmm, let me see something:

$ du -hs /usr/lib/ghc-6.12.3/
588M/usr/lib/ghc-6.12.3/

Wow!  That was unexpected. =)

$ du -sm /usr/lib/ghc-6.12.3/* | sort -n | tail -n 5
23  /usr/lib/ghc-6.12.3/template-haskell-2.4.0.1
24  /usr/lib/ghc-6.12.3/ghc
77  /usr/lib/ghc-6.12.3/Cabal-1.8.0.6
78  /usr/lib/ghc-6.12.3/base-4.2.0.2
265 /usr/lib/ghc-6.12.3/ghc-6.12.3

$ du -sm /usr/lib/ghc-6.12.3/ghc-6.12.3/* | sort -n | tail -n 5
1   /usr/lib/ghc-6.12.3/ghc-6.12.3/ZipDataflow.p_hi
30  /usr/lib/ghc-6.12.3/ghc-6.12.3/libHSghc-6.12.3-ghc6.12.3.so
43  /usr/lib/ghc-6.12.3/ghc-6.12.3/HSghc-6.12.3.o
56  /usr/lib/ghc-6.12.3/ghc-6.12.3/libHSghc-6.12.3.a
111 /usr/lib/ghc-6.12.3/ghc-6.12.3/libHSghc-6.12.3_p.a

Ah, so this one file alone takes 111 MiB =).  But 30 MiB of
libHSghc.so probably will need to be included.

$ xz -9  /usr/lib/ghc-6.12.3/ghc-6.12.3/libHSghc-6.12.3-ghc6.12.3.so | wc -c
4507512

So using one of the best generic compression algorithms available, the
size of one of the biggest libraries that a program using hint may
need comes down to 4.5 MiB.  Probably if someone is careful enough to
include only what really is necessary, the program installer will be
at most 10 MiB and will need at most 50 MiB on disk.  I think this is
doable, but a lot more than Lua; hint can't be used on set-top boxes
=).

 Sandboxing and import whitelisting with hint is also a no-brainer --
 see mueval and http://tryhaskell.org/. I also implement import
 filtering here with haskell-src-exts:
 http://github.com/chrisdone/haskell-json/blob/master/haskell-json.hs#L137
 So import whitelisting is trivial.

Sweet, I had forgotten about mueval.  And wouldn't it be nice if we
could hand haskell-src-exts's parse tree directly into GHC?

Cheers! =)

-- 
Felipe.
___
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 Felipe Lessa
On Tue, Aug 17, 2010 at 9:12 PM, Hemanth Kapila saihema...@gmail.com wrote:
   I was about to toss a coin to decide which one to pickup. Perhaps I should
 worry about the size.

You should think about what kind of code you want to support in your
scripts.  I mean, if you start binding every Haskell library into Lua,
maybe it would be better to have used hint =).

Cheers!

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


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

2010-08-15 Thread Felipe Lessa
On Sun, Aug 15, 2010 at 12:50 PM, Donn Cave d...@avvanta.com wrote:
 I wonder how many ByteString users are `working with bytes', in the
 sense you apparently mean where the bytes are not text characters.
 My impression is that in practice, there is a sizeable contingent
 out here using ByteString.Char8 and relatively few applications for
 the Word8 type.  Some of it should no doubt move to Text, but the
 ability to work with native packed data - minimal processing and
 space requirements, interoperability with foreign code, mmap, etc. -
 is attractive enough that the choice can be less than obvious.

Using ByteString.Char8 doesn't mean your data isn't a stream of bytes,
it means that it is a stream of bytes but for convenience you prefer
using Char8 functions.  For example, a DNA sequence (AATCGATACATG...)
is a stream of bytes, but it is better to write 'A' than 65.

But yes, many users of ByteStrings should be using Text. =)

Cheers!

-- 
Felipe.
___
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-14 Thread Felipe Lessa
On Sat, Aug 14, 2010 at 9:59 AM, Bill Atkins watk...@alum.rpi.edu wrote:
  | otherwise                                        = let (line, rest) = 
 splitAt maxLineLength line in
                                                                 line : 
 wrapLine rest

I haven't tested myself, but does this work at all?  If I am reading
it correctly, this is the same as

  let (foo, rest) = splitAt maxLineLength foo
  in foo : wrapLine rest

In other words, no mention of wrapLine's argument 'line', and a
recursive call that will bottom out and be the same as 'undefined' :).
 GHC would warn you, though, if you used -Wall.  That expression
should read:

  let (thisLine, rest) = splitAt maxLineLength line
  in thisLine : wrapLine rest

Cheers,

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


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

2010-08-13 Thread Felipe Lessa
On Fri, Aug 13, 2010 at 10:01 PM, Dan Doel dan.d...@gmail.com wrote:
 On Friday 13 August 2010 8:51:46 pm Evan Laforge wrote:
 I have an app that is using Data.Text, however I'm thinking of
 switching to UTF8 bytestrings.  The reasons are that there are two
 main things I do with text: pass it to a C API to display, and parse
 it.  The C API expects UTF8, and the parser libraries with a
 reputation for being fast all seem to have bytestring inputs, but not
 Data.Text (I'm using unpack - parsec, which is not optimal).

 You should be able to use parsec with text. All you need to do is write a
 Stream instance:

  instance Monad m = Stream Text m Char where
    uncons = return . Text.uncons

Then this should be on a 'parsec-text' package.  Instances are always
implicitly imported.

Suppose packages A and B define this instance separately.  If
package C imports A and B, then it can't use any of those
instances nor define its own.

Cheers! =)

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


Re: [Haskell-cafe] Couple of questions about *let* within *do*

2010-08-10 Thread Felipe Lessa
On Tue, Aug 10, 2010 at 1:40 PM, michael rice nowg...@yahoo.com wrote:
 1) Is there an implicit *in* before the last line above?

The (let ... in ...) construct is an expression, while the (let ...)
inside 'do' is a statement.  The (do ...) itself is an expression.
See the report:

http://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-440003.12
http://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-470003.14

 2) Within a do in the IO monad (or any other monad), can a *let* do
 something like this?

   let x = do   -- in a different monad

Yes =).  For example,

 main = do -- IO monad
   putStrLn Hello!
   let x = do i - [1..5] -- list monad (i.e. [])
  j - [i..5]
  return (i*j)
   mapM print x

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


Re: [Haskell-cafe] Couple of questions about *let* within *do*

2010-08-10 Thread Felipe Lessa
On Tue, Aug 10, 2010 at 2:40 PM, Bill Atkins batkin...@gmail.com wrote:
 They're not really statements, they're just named expressions and are still 
 subject to lazy evaluation.

 In:

  let x = putStrLn Name  getLine
  putStrLn Welcome
  x

Yes, 'putStrLn name  getLine' is an expression.  However, the
whole line 'let x = putStrLn Name  getLine' inside the
do-block is an statement.  Althought the word 'let' is used in
both cases, they are defined in different places of the grammar
(see the links of my previous mail).

So when you write

  do ...
 let ...  -- stmt
 ...

you are using a let statement.  You can use a let expression in a
do-block as well:

  do ...
 let ...
  in ... -- expr
 ...

Note, however, that you must indent the 'in' part, as you would
need to indent an if expression inside a do-block.

  do ...do {...
 let ... -- exprgets parsed as ;let ... -- stmt
 in ...  --;in ...  -- ???
 ...   ;...}

Cheers,

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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-10 Thread Felipe Lessa
On Tue, Aug 10, 2010 at 6:21 PM, Martijn van Steenbergen
mart...@van.steenbergen.nl wrote:
 On 8/2/10 7:09, Ertugrul Soeylemez wrote:

 Given the definition of a Haskell function, Haskell is a pure language.
 The notion of a function in other languages is not:

   int randomNumber();

 The result of this function is an integer.  You can't replace the
 function call by its result without changing the meaning of the program.

 I'm not sure this is fair. It's perfectly okay to replace a call
 randomNumber() by that method's *body* (1), which is what you argue is
 okay in Haskell.

Nope.  For example, suppose we have:

  int randomNumber(int min, int max);

Equivalentely:

  randomNumber :: Int - Int - IO Int

In Haskell if we say

  (+) $ randomNumber 10 15 * randomNumber 10 15

That's the same as

  let x = randomNumber 10 15
  in (+) $ x * x

If we had in C:

  return (randomNumber(10, 15) + randomNumber(10, 15))

That would not be the same as:

  int x = randomNumber(10, 15)
  return (x + x)

Cheers!

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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-10 Thread Felipe Lessa
On Tue, Aug 10, 2010 at 6:36 PM, Martijn van Steenbergen
mart...@van.steenbergen.nl wrote:
 On 8/10/10 23:27, Felipe Lessa wrote:

 If we had in C:

   return (randomNumber(10, 15) + randomNumber(10, 15))

 That would not be the same as:

   int x = randomNumber(10, 15)
   return (x + x)

 That's not fair. You're comparing C's '=' with Haskell's '='. But you should
 be comparing C's '=' with Haskell's '-'.

 In your Haskell example, x :: IO Int. In your C example, x :: Int.

Well, then maybe we will agree with eachother when we decide on what
is fair. =)

You quoted:

Given the definition of a Haskell function, Haskell is a pure language.
The notion of a function in other languages is not:

  int randomNumber();

The result of this function is an integer.  You can't replace the
function call by its result without changing the meaning of the program.

So, given the functions

  int randomNumber(int, int)
  randomNumber :: Int - Int - IO Int

what is replace the function call by its result?  Function call in C
is, for example,

  randomNumber(10, 15);

and the result of this call has type int.  In Haskell, what is a
function call?  Well, it's

  randomNumber 10 15

and the result is IO Int.  When we replace the function call by its
result, I think it is fair to replace the C function call by an int
and the Haskell function call by an IO Int, because that is what
those functions return.

To fit your definition of fairness I would have to say that function
application is

  \cont - randomNumber 10 15 = \x - cont x

which has type (Int - IO a) - IO a.  I don't think this is
function call at all, and only works for monads.

IMHO, Ertugrul was pointing out the difference of C's int and
Haskell's IO Int.  An 'IO Int' may be passed around and you don't
change the meaning of anything.

Cheers, =)

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


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

2010-08-08 Thread Felipe Lessa
On Sun, Aug 8, 2010 at 6:09 PM, Serguey Zefirov sergu...@gmail.com wrote:
 Except that we have to write real apps is a real gem of that conversation. 
 ;)

So this Anders guy bashes functional languages and then says that
programmers should be encouraged to write functional code in OO
languages?  Doesn't make any sense for me.  Well, whatever =).

Cheers! =)

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


Re: [Haskell-cafe] ANN: blaze-builder 0.1

2010-08-05 Thread Felipe Lessa
Sweet! =)

About the 'binary' package, does it speed up if you dump its own
Data.Binary.Builder and use the blaze builder?  Does it stay with the
same performance?

Thanks for working on blaze!

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


Re: [Haskell-cafe] Re: [web-devel] statically compiled css

2010-08-05 Thread Felipe Lessa
On Thu, Aug 5, 2010 at 9:41 AM, Tim Matthews tim.matthe...@gmail.com wrote:
 I have often wondered OK haml implemented now what about sass. Michael
 Snoyman what is your opinions on sass? Would a sass inspired syntax like you
 did with the haml-hamlet fit in well and if so, as it often best to keep
 styles separate, could a quasi quoted language live in in a separate haskell
 module and then at run time it recreates the separate css files on first
 launch?

A wholly statically-verified-by-the-compiler Web framework?!  We are
going to avoid success at all costs even more, I'd say. ;-)

Cheers!

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


Re: [Haskell-cafe] Playing with ATs again

2010-08-05 Thread Felipe Lessa
On Thu, Aug 5, 2010 at 7:18 AM, Ryan Ingram ryani.s...@gmail.com wrote:
 I actually think it's a
 testament to the quality of GHC that things just work so often that
 I can be so surprised when they don't.

Well said.  That's the feeling most Haskellers have, and that's part
of the awesomeness of programming with Haskell.

Cheers!

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


Re: [Haskell-cafe] Preview the new haddock look and take a short survey

2010-08-05 Thread Felipe Lessa
On Thu, Aug 5, 2010 at 10:48 AM, Johan Tibell johan.tib...@gmail.com wrote:
 One thing I haven't seen anyone else comment on is the width of the new
 docs. I have a large (26) monitor and use the browser full-screen (with
 xmonad, so even more screen space). When I load these pages, particularly
 the non-frame one, something like 50% of my screen real-estate is empty
 whitespace on either side of the doc content. There is also wasted space
 in the frames version, just a little less of it. I wish the docs were
 using that space like the current Haddock does. Is the plan to use a
 fixed width like this?

 Yes. There's research suggesting that the line length should be between 65
 and 75 characters per line.
 http://psychology.wichita.edu/surl/usabilitynews/42/text_length.htm

Perhaps on large monitors the Synopsis could auto-open to use the
available space?

My 2 cents, ;)

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


Re: [Haskell-cafe] ANNOUNCE: hierarchical-clustering and gsc-weighting

2010-08-04 Thread Felipe Lessa
On Tue, Aug 3, 2010 at 8:23 AM, Felipe Lessa felipe.le...@gmail.com wrote:
 On Tue, Aug 3, 2010 at 8:01 AM, Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com wrote:
 Felipe Lessa felipe.le...@gmail.com writes:
 'hierarchical-clustering' provides a function to create a dendrogram
 from a list of items and a distance function between them.  The most
 common linkage types are available: single linkage, complete linkage
 and UPGMA.  An item can be anything, for example a DNA sequence, so
 this may used to create a phylogenetic tree.

 What actual clustering algorithm are you using here?

 A naïve O(n^2) algorithm using a distance matrix.  This can be
 improved without changing the API, however.

What a blunder!  I mean, an O(n^3) algorithm -- each step takes
O(n^2), and you need 'n' steps to create the whole dendrogram.

I'll fix the documentation on the next release.

Cheers! =)

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


Re: [Haskell-cafe] ANNOUNCE: approximate-equality 1.0 -- Newtype wrappers for approximate equality

2010-08-03 Thread Felipe Lessa
On Tue, Aug 3, 2010 at 7:27 AM, Neil Brown nc...@kent.ac.uk wrote:
 I like the look of this.  Eq and Ord instances that use epsilon values look
 like they will be handy.  I have a design question/suggestion.  You have:

What properties does Eq need to obey?

Reflexivity: (a == a)
Symmetry: (a == b)  ==  (b == a)
Transitivity: ((a == b)  (b == c)) == (a == c)

An instance using epsilon values clearly is reflexive and symmetric,
but it is not transitive.

I've looked [1] and appearently Eq doesn't list the laws it should
satisfy, not even '(a == b) == not (a /= b)' is mentioned.

[1] 
http://haskell.org/ghc/docs/6.12.1/html/libraries/base-4.2.0.0/Prelude.html#t%3AEq

Cheers, =)

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


[Haskell-cafe] ANNOUNCE: hierarchical-clustering and gsc-weighting

2010-08-03 Thread Felipe Lessa
Hello!

I'm pleased to announce the release of two new packages:

http://hackage.haskell.org/package/hierarchical-clustering
http://hackage.haskell.org/package/gsc-weighting

'hierarchical-clustering' provides a function to create a dendrogram
from a list of items and a distance function between them.  The most
common linkage types are available: single linkage, complete linkage
and UPGMA.  An item can be anything, for example a DNA sequence, so
this may used to create a phylogenetic tree.

Or it may be used with the 'gsc-weighting' package to assign weights
to the items.  Weights are assigned such that close items get smaller
weight than distance items, meaning that the weights try to avoid the
over-representation of some closely related items.  The package name
come from the authors of the algorithm, Gerstein, Sonnhammer and
Chothia.  Again, this may be used for DNA or protein sequences.

Cheers!

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


Re: [Haskell-cafe] ANNOUNCE: hierarchical-clustering and gsc-weighting

2010-08-03 Thread Felipe Lessa
On Tue, Aug 3, 2010 at 8:01 AM, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:
 Felipe Lessa felipe.le...@gmail.com writes:
 'hierarchical-clustering' provides a function to create a dendrogram
 from a list of items and a distance function between them.  The most
 common linkage types are available: single linkage, complete linkage
 and UPGMA.  An item can be anything, for example a DNA sequence, so
 this may used to create a phylogenetic tree.

 What actual clustering algorithm are you using here?

A naïve O(n^2) algorithm using a distance matrix.  This can be
improved without changing the API, however.

 Also, would it be possible to have some more documentation there in
 general?  At the very least, in your next release explain what a
 dendogram is and why someone would want to use your package (I had to do
 some quick wikipedia looking to refresh my memory on what dendogram,
 etc. were to get an understanding of what it does).

Documentation is always good, but I didn't want to take the time to
explain everything from the beginning.  I guess most people coming to
this package will already know that they want a dendrogram.  But if
they don't, a quick googling is very effective.  Hmm, I guess some
diagrams would be nice.

I've took the time only to explain why there is an UPGMA and a
FakeAverageLinkage, because that distinction isn't easy to find on
the web.  Actually, I still haven't found someone talking about it,
just people using either with the same name average linkage. =)

Cheers,

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


Re: [Haskell-cafe] Reverse unification question

2010-08-02 Thread Felipe Lessa
On Mon, Aug 2, 2010 at 7:37 PM, Ryan Ingram ryani.s...@gmail.com wrote:
 there's no y.z that fulfills that requirement.  Lets rewrite in a
 System-F-style language with data types:
[...]
 So clearly x0 has type (C (A - r) r)
 However, our input is parametric in r, which is mentioned in x0's
 type, so we need to pass that parameter in.  Therefore, we end up
 with:

 (x :: /\r . C (A - r) r)

 Similar logic will show you that there is no z such that y.z :: /\r. C
 r r exists, since y.z must have type (C a (A - r)) for some type a.

Hello Ryan,

If I understood you correctly, there is such an x, and it has type

  x :: forall r. C (A - r) r

but there isn't such z.  Is that right?


To draw these conclusions I think it is possible to just use GHCi:

GHCi, version 6.12.3: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
Prelude :s -XExplicitForAll
Prelude :m -Prelude
 :m +Control.Category Data.Int
Control.Category Data.Int let y :: forall c r. c r (Int - r); y =
Prelude.undefined
Control.Category Data.Int let expected :: forall c r. c r r; expected
= Prelude.undefined
Control.Category Data.Int :t \x - (x . y) `Prelude.asTypeOf` expected
\x - (x . y) `Prelude.asTypeOf` expected
  :: (Category cat) = cat (Int - c) c - cat c c
Control.Category Data.Int :t \z - (y . z) `Prelude.asTypeOf` expected
\z - (y . z) `Prelude.asTypeOf` expected
  :: (Category cat) = cat (Int - b) b - cat (Int - b) (Int - b)


So if 'x' is of type 'cat (Int - r) r', then 'x . y' is of type 'cat
r r'.  That's what we wanted, that's what we got.

And if 'z' is of type 'cat (Int - r) r', then 'y . z' is of type 'cat
(Int - r) (Int - r)'.  Well, that's not what we really wanted.  But
we know that GHC infers the most general type as we are not using
rank-2 or rank-N functions, so we can't get 'cat r r' from 'y . z' for
all 'z'.

Am I being too sloppy here? =)

Cheers,

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


Re: [Haskell-cafe] Laziness question

2010-08-01 Thread Felipe Lessa
On Sun, Aug 1, 2010 at 11:29 AM, Nicolas Pouillard
nicolas.pouill...@gmail.com wrote:
 Finally maybe we can simply forbidden the forcing of function (as we do with
 Eq). The few cases where it does matter will rescue to unsafeSeqFunction.

What's the problem with

  class Eval a where
seq :: a - t - t

  instance Eval b = Eval (a - b) where
seq f = seq (f undefined)

It would reduce at least to WHNF as unsafeSeq would.  Does it compute
more than WHNF?

Hmmm, I see, if we had

  f :: Int - Int
  f _ = undefined

Then my seq above would diverge while unsafeSeq wouldn't.  Perhaps
that instance would be a good compromise if we insist in not using
'unsafeSeq' to define it.

Cheers, =)

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


Re: [Haskell-cafe] ANNOUNCE: Takusen 0.8.6

2010-08-01 Thread Felipe Lessa
On Sun, Aug 1, 2010 at 6:58 PM, Jason Dagit da...@codersbase.com wrote:
 This same issues comes up fairly often on the darcs-users mailing list.  My
 understanding of the way things are handled there, is that if there is ever
 a good reason to drop support for a version of GHC then the person who wants
 to drop support is supposed to look and see what is in Debian stable.  If
 debian stable is still covered after the proposed changes then they are
 accepted automatically.  If Debian stable would not be covered, then there
 is a discussion to reach consensus.
 The reasons it works are: a) support is dropped lazily when there is a real
 demand to do so, instead of artificially; b) letting people discuss it
 case-by-case allows the decision to be made with full context.

Do you know if they test on GHC 6.8?  Or do they just avoid extensions
and hope it works? =)

Cheers,

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


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

2010-07-31 Thread Felipe Lessa
On Sat, Jul 31, 2010 at 5:23 PM, David Leimbach leim...@gmail.com wrote:
 Does Singularity also have such back doors?

The CLR doesn't load machine code, it loads bytecodes.  So it is
possible to statically analyse the module and see hmmm, this module
uses unsafePerformIO, I'll reject it.  If the bytecode is ok, only
then it is JITed into efficient machine code.

And note that we wouldn't need unsafePerformIO for the FFI if all
programs were made in Haskell ;).

Cheers,

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


Re: [Haskell-cafe] Class instances on class constraints

2010-07-28 Thread Felipe Lessa
2010/7/28 Dušan Kolář ko...@fit.vutbr.cz:
 which does not work, of course (Flexible or Undecidable instances won't
 help). The aim is to have addElem function that works differently according
 to situation whether a type, which is base of the list/set, is a member of
 class Eq or Ord. Could you point me or hint me how to get as close as
 possible to the required solution? Maybe I'm not able to see an obvious
 way...

Use the good'ol trick:

newtype ByEq a = ByEq {unByEq :: a}
newtype ByOrd a = ByOrd {unByOrd :: a}

instance (Eq a) = SetOL (ByEq a) where
  addElem = addEq . unByEq

instance (Ord a) = SetOL (ByOrd a) where
  addElem = addOrd . unByOrd

Cheers,

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


Re: [Haskell-cafe] Need Control.Monad.State

2010-07-27 Thread Felipe Lessa
On Wed, Jul 28, 2010 at 12:04 AM, Ivan Miljenovic
ivan.miljeno...@gmail.com wrote:
 On 28 July 2010 13:03, michael rice nowg...@yahoo.com wrote:

 [mich...@localhost ~]$ ghc-pkg list mtl
 /usr/lib/ghc-6.12.1/package.conf.d
 [mich...@localhost ~]$

 Installed?

 No; if it was installed it would specify a version.

For example:

$ ghc-pkg list mtl
/usr/lib64/ghc-6.12.3/package.conf.d
   mtl-1.1.0.2

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


Re: [Haskell-cafe] ANN: weighted-regexp-0.1.0.0

2010-07-26 Thread Felipe Lessa
Wow, great paper!  I got somewhat scared when I saw the first
description of the scene, but after I started reading I couldn't stop
anymore =D.

Thanks,

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


Re: [Haskell-cafe] 1st attempt at parallelizing

2010-07-26 Thread Felipe Lessa
2010/7/26 Günther Schmidt gue.schm...@web.de:
 Hi all,

Hello!

 I'm spidering web pages, the implementation currently is synchronous. I'd
 like to parallelize this for speed-up, ie. get up to 6 pages in parallel and
 recycle those threads.

This is usually called concurrent programming, not parallel.

 Now I have come across good examples for this on the web before, but I doubt
 I'd find it again right away.

 I'd appreciate some good pointers.

There's a simple way of doing this with Chans, for example:

import Control.Applicative
import Control.Concurrent.STM
import Control.Monad
import qualified Data.Map as M

data Page = ...
data Info = ...

download :: Page - IO Info
download = ...

getOneByOne :: [Page] - IO (M.Map Page Info)
getOneByOne = M.fromList $ mapM (\p - (,) p $ download p)

downloader :: TChan (Maybe Page) - TChan (Page, Info) - IO ()
downloader in out = do
  mp - atomically (readTChan in)
  case mp of
Nothing - return ()
Just p - download p = atomically . writeTChan out

getConcurrent :: Int - [Page] - IO [M.Map Page Info]
getConcurrent n xs = do
  in - newTChanIO
  out - newTChanIO
  replicateM_ n (forkIO $ downloader in out) -- create n threads
  mapM (writeTChan in . Just) xs
  replicateM_ n (writeTChan in Nothing) -- kill n threads
  M.fromList $ mapM (\_ - readTChan out) xs


This code doesn't take exceptions into account, which you should, but
this works.  Well, I guess, didn't try, if it compiles then it should
;).

HTH,

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


Re: [Haskell-cafe] 1st attempt at parallelizing

2010-07-26 Thread Felipe Lessa
2010/7/26 Felipe Lessa felipe.le...@gmail.com:
 downloader :: TChan (Maybe Page) - TChan (Page, Info) - IO ()
 downloader in out = do
  mp - atomically (readTChan in)
  case mp of
    Nothing - return ()
    Just p - download p = atomically . writeTChan out

Oops!  Of course there should be recursion here!  (This is a bug the
typechecker probably wouldn't catch.)

downloader :: TChan (Maybe Page) - TChan (Page, Info) - IO ()
downloader in out = do
 mp - atomically (readTChan in)
 case mp of
   Nothing - return ()
   Just p - download p = atomically . writeTChan out  downloader in out

Cheers,

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


Re: [Haskell-cafe] Regular Expression to Determinate Finite Automata translator

2010-07-22 Thread Felipe Lessa
Some comments:

- You can run your code thru HLint, here it gives me 27 suggestions.

- Why don't you derive the Show instance for RE instead of writing it
by yourself?

- Note that

  do x
 do y
...

is the same as

  do x
 y
 ...

- You can parametrize RE as

  data RE s p = Epsilon
  | Leaf Char s p
  | Selection (RE s p) (RE s p)
  | Sequence  (RE s p) (RE s p)
  | Kleene(RE s p)
  | Optional  (RE s p)
  | End s
  deriving (Show)

  type RE1 = RE () ()
  type RE2 = RE State ()
  type RE3 = RE State Pos


Cheers! =)

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


Re: [Haskell-cafe] ANNOUNCE: Haskell Platform 2010.2.0.0

2010-07-22 Thread Felipe Lessa
On Thu, Jul 22, 2010 at 9:00 PM, Don Stewart d...@galois.com wrote:
 We're pleased to announce the fifth release of the Haskell Platform: a
 single, standard Haskell distribution for everyone.

That's just great, dons!  Thanks a lot!

Cheers, =)

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


Re: [Haskell-cafe] Please report any bug of gtk2hs-0.11.0!

2010-07-19 Thread Felipe Lessa
Err... where is pixbufFromImageSurface [1] now?  I have an old program
that draws using cairo an static diagram to a pixbuf which then
becomes the backend of an Image.  If pixbufFromImageSurface got
deprecated, what's a better solution?

[1] 
http://www.haskell.org/gtk2hs/docs/gtk2hs-docs-0.10.0/Graphics-UI-Gtk-Cairo.html#v%3ApixbufFromImageSurface

Cheers!

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


Re: [Haskell-cafe] How do you make constant expressions?

2010-07-18 Thread Felipe Lessa
On Sun, Jul 18, 2010 at 5:19 PM, Eitan Goldshtrom
thesource...@gmail.com wrote:
 Silly question, but I can't find the answer on the net. I think I'm just
 using the wrong words in my search. I'm looking for a way to create constant
 expressions in Haskell. The C/C++ equivalent of what I'm talking about is

 #define NAME VALUE

 I want an expression, or really just numbers for what I'm doing, that the
 compiler will put into the program at the designated places, instead of
 storing it in memory like a variable.

Unless you want to pattern match the value, just say

  myconst :: Double -- or anything else
  myconst = 7.14
  {-# INLINE myconst #-}

Voilà!

This doesn't work for pattern matching, however, if you say

  f myconst = ...

then 'myconst' will be the name of that argument that could be
anything, and not just 7.14.

You could, however, use CPP as well

  {-# LANGUAGE CPP #-}
  #define MYCONST 7.14

  f MYCONST = ...

but I'm against using CPP unless you need it.

Cheers,

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


Re: [Haskell-cafe] RE: Design for 2010.2.x series Haskell Platform site (Don Stewart)

2010-07-17 Thread Felipe Lessa
On Sat, Jul 17, 2010 at 2:23 PM, Christopher Done
chrisd...@googlemail.com wrote:
 Anyway, fantastic! What does everyone else think?

I like it as well.  There are only two nitpicks: I think that icon for
Linux is lame, and I get confused by the image of the guy diving.

Thanks, =)

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


Re: [Haskell-cafe] is this a bug ?

2010-07-16 Thread Felipe Lessa
You should probably CC the maintainer of the regex package.

Cheers,

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


Re: [Haskell-cafe] trees and pointers

2010-07-15 Thread Felipe Lessa
On Thu, Jul 15, 2010 at 4:30 AM, Stephen Tetley
stephen.tet...@gmail.com wrote:
 2010/7/15 Jake McArthur jake.mcart...@gmail.com:
 On 07/14/2010 05:01 PM, Victor Gorokhov wrote:

 You can implement pure pointers on top of Data.Map with O(log n) time

 Or on top of Data.IntMap with O(1) time. ;)

 Unlikely...

 From the docs, lookup is O(min(n,W))

W is a constant, 32 or 64 on most machines, so this is really O(W) = O(1).

Should someone create an IntegerMap, then lookup wouldn't be O(1) as W
would be variable.

Cheers!

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


Re: [Haskell-cafe] passing a polymorphic function as a parameter vs using it directly in a function definition

2010-07-15 Thread Felipe Lessa
On Thu, Jul 15, 2010 at 9:20 AM, Pasqualino Titto Assini
tittoass...@gmail.com wrote:
 Many thanks for the explanation.

 But I thought that GHC always derives the most generic type, why does
 it fix my 'a' to 'Int' ?

Inferring the type of higher ranked functions is problematic, so GHC
never does this by itself.  See [1].

[1] 
http://www.haskell.org/ghc/docs/6.12.1/html/users_guide/other-type-extensions.html#id3027672

HTH,

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


Re: [Haskell-cafe] Applying a value to a function generically

2010-07-14 Thread Felipe Lessa
On Wed, Jul 14, 2010 at 8:25 AM, Arnaud Bailly arnaud.oq...@gmail.com wrote:
 Hello,
 I would like to construct a collection of function-like objects on
 which I could apply some value, in a typesafe and clean way.

You could use Data.Typeable.cast [1]

[1] 
http://haskell.org/ghc/docs/6.12.1/html/libraries/base-4.2.0.0/Data-Typeable.html#v%3Acast

 Let's say I have something like this:

 data Fun = forall a b . F (a  - b)
 type Callables = Map String Fun

Sorry, but using GADT syntax:

  data Fun where
F :: (Typeable a, Typeable b) = (a - b) - Fun

 I would like to be able to write:

 invoke :: Callables - a - String - b
 invoke m d k = case lookup k m of
  Just (F f) - f d
  Nothing   - error $ unable to find function for key  ++ k

Untested:

  invoke :: (Typeable a, Typeable b) = Callables - a - String - Maybe b
  invoke m d k = do
F f - lookup k m
arg - cast d
cast (f arg)

HTH!

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


Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: Haskell 2010 Report (final)

2010-07-12 Thread Felipe Lessa
On Mon, Jul 12, 2010 at 9:50 AM, Simon Marlow marlo...@gmail.com wrote:
 And hopefully things will improve over time, as fewer packages will need to
 depend on base.  We could also start pulling out APIs that are currently in
 base into separate packages, without actually pulling out the code - e.g.
 concurrency, and that would be a good way to migrate people away from
 depending on base, but without breaking everything.

Is the plan to stop using base and start using 'haskell2010', even if
you use extensions that aren't Haskell 2010?

Cheers!

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


Re: [Haskell-cafe] Actually loading a Cabal package in GHCi

2010-07-11 Thread Felipe Lessa
On Sun, Jul 11, 2010 at 2:05 PM,  d...@patriot.net wrote:
 OK, I know this is a newbie kind of thing (I guess I am a newbie to GHCi).
  I've been over and over and over the wiki and I just can't find the
 answer to this very, very elementary question.  How can I load a package
 that I've downloaded using Cabal into GHCi?  When I do the :l, it just
 doesn't see the thing.  On one level, this is clear: the downloaded Cabal
 packages (yes, more than one) are under .cabal in $HOME and not in the
 lib/ghc area.  OK, fine.  But there's no package data base to point to so
 that the packages can be loaded.

 This just *has* to be a simple thing, but I just can't find it, no matter
 how flat my head gets beating against the wall.  I apologize for the
 density of my skull, but can someone point me in the right direction here?

GHCi automatically loads the package, you just need to put the modules
into scope.  This is analogous to using an import declaration.  For
example:

GHCi, version 6.10.4: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
Prelude :m Data.ByteString.Char8
Prelude Data.ByteString.Char8 pack hello
Loading package bytestring-0.9.1.4 ... linking ... done.
hello
Prelude Data.ByteString.Char8 pack hello
hello

So, just put the modules you want into scope with

  :m Module1 Module2 ...

or

  :m Module1
  :m +Module2 Module3
  :m +Module4 Module5

That should get you started =).

Cheers,

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


Re: [Haskell-cafe] Re: The site has been exploited (again)

2010-07-11 Thread Felipe Lessa
On Sun, Jul 11, 2010 at 2:37 PM, Gour g...@gour-nitai.com wrote:
 This is not good advertisement for Haskell and maybe it's time to
 deploy more-secure Haskell web apps/frameworks...

As far as I know, haskell.org doesn't run on top of Haskell software.

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


Re: [Haskell-cafe] Other transactional arrays?

2010-07-09 Thread Felipe Lessa
On Fri, Jul 9, 2010 at 7:16 AM, Emil Melnicov emilm...@gmail.com wrote:
 writeTVector :: TVector a - Int - a - STM ()
 writeTVector (TVector t#) (I# i#) x = stm $ \s1# -
     case readTVar# t# s1#                    of { (# s2#, (MutableArray a#) 
 #) -
     case writeArray# a# i# x s2#             of { s3# -
     case writeTVar# t# (MutableArray a#) s3# of { s4# -
     (# s4#, () #) }}}

 It seems like it works, but I'm in doubt about it's correctness.
 Unfortunately, I don't know much about STM mechanics, so I'm asking
 Cafe users (you :-) for help.

I guess the only problem lies with writeTVector.  I don't know much
about STM implementation details as well, but reading the code for
writeTVector I can't see how it could be rollbacked.  I.e., should
something with writeTVector fail and rollback, how will the old value
get into the mutable array?

Cheers :)

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


Re: [Haskell-cafe] C9 video on monads and coordinate systems

2010-07-08 Thread Felipe Lessa
On Wed, Jul 7, 2010 at 8:00 PM, Greg Meredith
lgreg.mered...@biosimilarity.com wrote:
 Dear Haskellians,
 You may be interested in this video i did with Brian Beckman on monads,
 location and coordinate systems.

Great, nice jamming! I wonder what's the URL of the Haskell code you
have, however :).

Cheers,

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


Re: [Haskell-cafe] Canonical Graphviz code

2010-07-06 Thread Felipe Lessa
On Tue, Jul 6, 2010 at 7:15 PM, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:
 As such, I probably won't be implementing the canonical form stuff any
 time soon in graphviz, and might need to examine Graphviz's source code
 to compare it and ensure that it's at least similar :s

I'm sorry for being silly, but what's the motivation of having this
canonic form? =)

Cheers!

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


Re: [Haskell-cafe] Canonical Graphviz code

2010-07-06 Thread Felipe Lessa
On Tue, Jul 6, 2010 at 7:53 PM, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:
 Felipe Lessa felipe.le...@gmail.com writes:
 I'm sorry for being silly, but what's the motivation of having this
 canonic form? =)

 A few things come to mind:

 * Easier to reason about, [...]
 * Less ambiguity: [...]

So you want to do some post-processing to the Dot graph inside
Haskell-land?  Or is it just a pretty printer?  I mean, Dot will
accept both and produce the same result (by definition), so if you
just wanted to draw it then there wouldn't be any difference.

Cheers! :)

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


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

2010-07-05 Thread Felipe Lessa
On Mon, Jul 5, 2010 at 6:12 AM, Ertugrul Soeylemez e...@ertes.de wrote:
 Felipe Lessa felipe.le...@gmail.com wrote:

 On Sat, Jul 3, 2010 at 9:25 AM, Ertugrul Soeylemez e...@ertes.de wrote:
  Haskell provides a lot of low level glue like laziness, currying and
  other very helpful language features.  But what is different in
  Haskell is that it doesn't seem to provide any high level glue like
  other languages do, especially when it comes to the IO world.  There
  is a somewhat powerful module system, but nothing to bring modules
  and the objects they define together in a consistent way.

 When I first read this paragraph, I thought: STM to the rescue!.
 STM is one of the best concurrent world glues, IMHO.

 I found that I get along with the basic concurrency constructs.  STM may
 be handy in a few applications, but in none that I write.

STM has the same basic concurrency constructs, but they are safe to
use.  MVars and everything derived from them have tricky semantics
that can fail in catastrofic ways.  Neil Mitchell was recently trying
to find a subtle bug in his code because of MVars and Chans.

Cheers!

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


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

2010-07-05 Thread Felipe Lessa
On Mon, Jul 5, 2010 at 10:29 AM, Ertugrul Soeylemez e...@ertes.de wrote:
 It happened once to me that I forgot that MVars don't have a queue.  A
 database thread would take values out of the MVar as commands and
 execute them, but I used the same thread to put a command into the MVar
 (for later execution).  It worked most of the time, unless another
 thread put a command concurrently, right after the last command was
 executed and before the database thread put another command ⇒ deadlock.

 I fixed this by replacing the MVar by a Chan.  Could STM have helped
 here?

Probably only if both puts were in the same transaction, I guess.
Even with STM the solution is a channel, i.e. TChan.

 And as a related question, how fast does STM perform in average?
 Is it suitable for high traffic applications (not network/file traffic,
 but MVar/Chan traffic)?  Usually in a non-SMP setting I can easily pass
 hundreds of thousands of values per second through MVars between tens of
 thousands of threads.

As always, I guess you should benchmark :).  There is some overhead,
indeed, however for most applications I guess it should be fine.
Specially because that overhead comes to save you from a lot of
headaches.

Cheers,

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


Re: [Haskell-cafe] Re: Suggestions for an MSc Project?

2010-07-04 Thread Felipe Lessa
On Sun, Jul 4, 2010 at 7:03 AM, John Smith volderm...@hotmail.com wrote:
 On 04/07/2010 12:00, Ivan Lazar Miljenovic wrote:
 Have a look through the wish-list here:
 http://www.reddit.com/r/haskell_proposals/

 Thanks, I had a look at the list, but none of it seems to be appropriate for
 a medium-length academic project with real-world benefits.

What about [1]?  Such a graphical editor could be used, for example,
for an EDSL.  =D

Cheers,

[1] 
http://www.reddit.com/r/haskell_proposals/comments/9n8nc/write_a_scratchlike_graphical_editor_for_a/

-- 
Felipe.
___
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 Felipe Lessa
On Sat, Jul 3, 2010 at 9:25 AM, Ertugrul Soeylemez e...@ertes.de wrote:
 Haskell provides a lot of low level glue like laziness, currying and
 other very helpful language features.  But what is different in Haskell
 is that it doesn't seem to provide any high level glue like other
 languages do, especially when it comes to the IO world.  There is a
 somewhat powerful module system, but nothing to bring modules and the
 objects they define together in a consistent way.

When I first read this paragraph, I thought: STM to the rescue!.
STM is one of the best concurrent world glues, IMHO.

 In my opinion this is both a disadvantage and an advantage.  It's bad
 because there is no standard way of gluing, nothing everybody learns and
 uses.  On the other hand it's good, because you can make your own glue.
 This has proven very useful for me.  My usual way is writing monad
 transformers and sticking them together, often together with concurrent
 programming.

Oh, so it is about monad transformers.  =)

If you want, you may use Haskell just as you as PHP or C: just put
everything in IO.  Your code will get uglier and the type system won't
catch many bugs, but that's what we get when doing C or PHP, right?

 The problem with that approach is:  This makes my code harder to
 understand for beginners.  Usually they can tell /what/ my code is
 doing, because it's written in natural language as much as possible, but
 they couldn't reproduce it.  And when they try to learn it, they give up
 fast, because you need quite some background for that.  Also sometimes
 when I write Haskell, my friend sits beside me and watches.  When he
 asks (as a PHP programmer with some C background), say, about my types,
 I can't give a brief explanation like I could in other languages.

I agree that it gets harder to reason about the code.  In fact,
sometimes I stack monad transformers in the wrong order.  However, as
Ivan says, if the feature is useful for you, don't be afraid of using
it.  Beginners may have a hard time grasping the concepts for the
first time, but that's only until they get it.

About monad transformers, I don't really like to use them because they
can get hairy in some cases, and because they have poor performance in
other cases.  Yet the decision of using transformers or not should be
made depending on your particular needs.

 Yesterday I was writing a toy texture handler for OpenGL (for loading
 and selecting textures).  He asked about my TextureT type.  I couldn't
 explain it, because you couldn't even express such a thing in PHP or C.

  type TextureT = StateT Config

  -- Note that this is MonadLib.
  -- BaseM m IO corresponds to MonadIO m.
  selectTexture :: BaseM m IO = B.ByteString - TextureT m ()

It is the type of functions that may access and modify a state of type Config.

Cheers,

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


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

2010-07-03 Thread Felipe Lessa
On Sat, Jul 3, 2010 at 9:43 AM, Daniel Fischer daniel.is.fisc...@web.de wrote:
 Andrew Coppin:
  Who says they do, or should?

 Don, a few emails ago.

 I think you missed a small detail there.

 ivan.miljenovic:
   Hmm, interesting. Applicative and Traversable are two classes I've
   never   used and don't really understand the purpose of. I have no
   idea what hsc2hs is. I keep hearing finger trees mentioned, but
   only in connection to papers that I can't access. So I guess that
   means that I don't count as a knowledgable Haskell programmer.
   :-(
  
   RWH is free and online, and covers many useful things. There's no
   excuse :-)
 
  Knowing about something /= knowing how to use it.  I own and have read
  RWH, but I've never had to use hsc2hs, or Applicative, etc.

 Writing libraries that bind to C is a great way to have to use a lot of
 hsc2hs (or c2hs), so clearly you need to contribute more libraries :-)

 dons was replying to *Ivan Miljenovic* here (with a smiley to remove all
 doubt), he was teasing [is that the entirely correct word?] Ivan a bit.

Ohhh, so that's the quotation being discussed?  I can not speak for
dons, but I understood that he meant that more bindings should be
contributed, really.  Don't get wrong, I love Haskell-only code, but
the reality is that reinventing the wheel isn't fun most of the time.

For example, I have two bindings on Hackage [1,2].  We could write a
2D physics library in pure Haskell, and I think there was a project
some time ago to write a 3D one, but that's a tough job.  It is
difficult to get right, and difficult to be fast enough to be useful.
Chipmunk already exists, uses the MIT license and is heavily
optimized.  The optimization package would be even easier to rewrite
in pure Haskell, but if you look at the API docs [3] you'll see that
the C library handles a lot of corner cases and has many knobs to get
the most out of the optimization proccess.  In fact, the C library was
written by the authors of the optimization procedure, so it probably
has very few bugs.  Repeating everything in Haskell would be a pain.

There are many many other useful C libraries that we should have
bindings to.  For example, Hackage doesn't have any MPI bindings.
Could we write an MPI client in Haskell?  I guess so.  Is it worth it?
I doubt.

Cheers!

[1] http://hackage.haskell.org/package/Hipmunk
[2] http://hackage.haskell.org/package/nonlinear-optimization
[3] 
http://hackage.haskell.org/packages/archive/nonlinear-optimization/0.3.2/doc/html/Numeric-Optimization-Algorithms-HagerZhang05.html

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


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

2010-07-03 Thread Felipe Lessa
On Sat, Jul 3, 2010 at 10:15 AM, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:
 Felipe Lessa felipe.le...@gmail.com writes:
 There are many many other useful C libraries that we should have
 bindings to.  For example, Hackage doesn't have any MPI bindings.
 Could we write an MPI client in Haskell?  I guess so.  Is it worth it?

 We might get some in two weeks time shameless plugat AusHac/shameless
 plug!!! http://www.haskell.org/haskellwiki/AusHac2010#MPI_bindings

That's nice!  There are many interesting possibilities of high-level
bindings that may be explored.  I've mentioned MPI because I may need
such bindings in a not-so-near future.

I'll also note that having many bound libraries is also an advantage
for newcomers.  If they see that a library they use to solve problems
in other languages already has a binding for Haskell, then they are
much more likely to be successful and in a shorter time.  I, for one,
didn't have to learn anything new at all to use Gtk2Hs (thanks,
guys!).  Should we have only WxWidgets bindings then I would need to
learn the Wx way before writing my first graphical program.  (Alas,
I've never programmed with Gtk+, the C bindings, I've learnt with
Gtk# and then PyGtk.)

Cheers,

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


Re: [Haskell-cafe] Rank2Types and pattern matching

2010-07-03 Thread Felipe Lessa
Hello!

On Sat, Jul 3, 2010 at 9:12 PM, Dan Doel dan.d...@gmail.com wrote:
 The problem is instantiation. SomeMonad is a constructor for the type

  SomeMonad s a

 for any *particular* s and a. But the type:

  forall s. SomeMonad s a

 is not that type. That type doesn't have constructors (proper) at all, and
 hence you cannot match against it. If types were passed explicitly, then
 values of the second type would look like:

  /\s - ...

 Where the big lambda is type abstraction. But you can't match against this, of
 course (just as you can't match against functions as lambda expressions), you
 can only apply values of this type.

I understood your explanation.  However, is this an implementation
detail/bug or is it an intended feature?

Cheers,

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


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

2010-06-30 Thread Felipe Lessa
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 developer or three.  How easy is this?  I'd
 appreciate replies from people who have actually done this.

I guess it must be a lot easier to find applicants if you don't
require them to live in the same city/country as you.

Cheers,

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


Re: [Haskell-cafe] The mother of all functors/monads/categories

2010-06-27 Thread Felipe Lessa
On Sun, Jun 27, 2010 at 10:54:08AM +0100, Max Bolingbroke wrote:
 Example 2: Codensity is the mother of all Monads

I thought the continuation monad was the mother of all monads. :)
For example, see [1].

Cheers!

[1] http://blog.sigfpe.com/2008/12/mother-of-all-monads.html

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


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

2010-06-26 Thread Felipe Lessa
On Sat, Jun 26, 2010 at 09:29:29AM +0300, Roman Beslik wrote:
 Incorrect encoding of filepaths is common in e.g. Cyrillic Linux
 (because of multiple possible encodings --- CP1251, KOI8-R, UTF-8)
 and is solved by fiddling with the current locale and media mount
 options. No need to change a program, or to tell character encoding
 to a program. It is not a programming language issue.

If your program saves files using filepaths given by the user or
created programatically from another filepath, then you don't
need to decode/encode anything and the problem isn't in the
programming language.

However, suppose your program needs to create a file with a name
based on a database information.  Your database is UTF-8.  How do
you translate that UTF-8 data into a filepath?  This is the
problem we got in Haskell.  We have a nice coding-agnostic String
datatype, but we don't know how to create a file with this very
name.

The opposite also may also be problem.  Okay, you got an already
correctly-encoded filepath.  But you want to store this
information in your database.  Now, you have two options:

  a) Save the enconded filepath.  Each record of your database
  will potentially have a different encoding, which is very bad.

  b) Recode into, say, UTF-8.  But to do that you need to know
  the original coding using in the filepath, so we got the same
  problem above.

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.

Cheers,

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


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

2010-06-26 Thread Felipe Lessa
On Sat, Jun 26, 2010 at 04:48:39PM +0400, Bulat Ziganshin wrote:
 Saturday, June 26, 2010, 4:44:20 PM, Felipe Lessa 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 ;)

Of course there is, however we should use the least common
denominator if we want to create portable programs.  Even if
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.

Cheers,

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


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

2010-06-26 Thread Felipe Lessa
On Sat, Jun 26, 2010 at 05:01:06PM +0400, Bulat Ziganshin 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

Now we got back on topic! :)

The FilePath datatype is OS-dependent and making it abstract
should be at least a first step.  If you got it from somewhere
else where it is already encoded, then fine.  If you need to
construct it, then you need to use a smart constructor.  If you
need to show/print it, then you need to convert it to String.
And so on.

Cheers,

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


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

2010-06-26 Thread Felipe Lessa
On Sat, Jun 26, 2010 at 05:34:49PM +0400, Alexey Khudyakov wrote:
 It should solve most of problems I believe. But such change will break
 a lot of programs maybe most of them. How could one introduce such a
 change? One variant is to create new hierarchy and gradually deprecate
 old.

 Also same problem affect command line arguments and process module.

So that means we should make this change as soon as possible,
doesn't it? :)

The problem now is designing a future-proof OS-agnostic API to
avoid having to change this core part of the base library again
in the near future.

Cheers,

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


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

2010-06-26 Thread Felipe Lessa
On Sun, Jun 27, 2010 at 02:55:33AM +0300, Roman Beslik wrote:
  On 26.06.10 15:44, Felipe Lessa wrote:
 However, suppose your program needs to create a file with a name
 based on a database information.  Your database is UTF-8.  How do
 you translate that UTF-8 data into a filepath?  This is the
 problem we got in Haskell.  We have a nice coding-agnostic String
 datatype, but we don't know how to create a file with this very
 name.

 It is simple — you recode from (database | network server | file)
 encoding to the current locale.

Recoding is indeed very simple.  You know the source coding
(e.g. your database is in UTF-8).  But how do you discover the
target coding?  How can you find out that this system uses
ISO8859-1, while this other one uses UTF-16, while...?

See the problem now? :)

Cheers,

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


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

2010-06-26 Thread Felipe Lessa
On Sun, Jun 27, 2010 at 02:52:54AM +0300, Roman Beslik wrote:
  On 26.06.10 16:34, Alexey Khudyakov wrote:
 On Sat, 26 Jun 2010 10:14:50 -0300
 Felipe Lessafelipe.le...@gmail.com  wrote:
 On Sat, Jun 26, 2010 at 05:01:06PM +0400, Bulat Ziganshin wrote:
 but what you propose cannot be used in Windows at all! while current
 FilePath still works on Unix, with manual filenames en/decoding
 Now we got back on topic! :)
 
 The FilePath datatype is OS-dependent and making it abstract
 should be at least a first step.  If you got it from somewhere
 else where it is already encoded, then fine.  If you need to
 construct it, then you need to use a smart constructor.  If you
 need to show/print it, then you need to convert it to String.
 And so on.
 
 It should solve most of problems I believe. But such change will break
 a lot of programs maybe most of them. How could one introduce such a
 change? One variant is to create new hierarchy and gradually deprecate
 old.

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

For example, this program would break:

  import System.Environment (getArgs)

  main :: IO ()
  main = getArgs = \[a] - writeFile a hello world

The types are:

  getArgs   :: IO [String]
  writeFile :: FilePath - String - IO ()

Right now we have

  type FilePath = String

so the code above works.  If we had

  data FilePath = ...

then that would be a type error work at all.  So even one of the
most trivial programs wouldn't compile anymore.

Cheers,

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


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

2010-06-26 Thread Felipe Lessa
On Sat, Jun 26, 2010 at 10:01:57PM -0300, Felipe Lessa wrote:
 The types are:

   getArgs   :: IO [String]
   writeFile :: FilePath - String - IO ()

On a similar note, getArgs probably suffers from the same
problem.  Which should it be?

  a) getArgs :: IO [String]
  b) getArgs :: IO [Word8]
  c) getArgs :: IO [FilePath]
  d) getArgs :: IO [Argument]

Cheers,

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


Re: [Haskell-cafe] Construction of short vectors

2010-06-25 Thread Felipe Lessa
On Fri, Jun 25, 2010 at 12:41:48AM +0400, Alexey Khudyakov wrote:
 Then constructor like one below arise naturally. And I don't know how to write
 them properly. It's possible to use fromList but then list could be allocated
 which is obviously wasteful.

Did you see the generated core?  I think you should give a try to
the following simple code:

  import qualified Data.Vector.Generic as VG -- vector == 0.6.*

  vector2 :: Double - Double - Vec2D
  vector2 x y = Vec2D (VG.fromListN 2 [x,y])

 Another question is there any specific problems with short vectors? They could
 be just 2 elements long. I mean performance problems

Probably there will be more overhead than defining

  data Vec2D = Vec2D {-# UNPACK #-} !Double
 {-# UNPACK #-} !Double

You should profile to see how much difference there is between
those representations.

Cheers,

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


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

2010-06-23 Thread Felipe Lessa
On Thu, Jun 24, 2010 at 02:35:55AM +0200, Günther Schmidt wrote:
 Is that something that MonadFix is meant to be used for?

In current Gtk libraries, no.  You'll do something like

  do btns - mapM createBtn [1..4]
 mapM_ connect $ zip btns (tail $ cycle btns)

However, if some library required you to supply the action while
constructing the button, then I guess the answer would be yes.

Cheers,

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


Re: [Haskell-cafe] Tiger compiler: variable escaping analysis phase

2010-06-22 Thread Felipe Lessa
On Tue, Jun 22, 2010 at 09:33:22AM -0300, José Romildo Malaquias wrote:
 In the variable escaping analysis phase of the compiler, a function
 findEscape looks for escaping variables and record this information in
 the escape fields of the abstract syntax. To do this the entire abstract
 syntax tree is traversed looking for escaping uses of every variable,
 and, when found, the field is set to true.

 findEscape uses a symbol table to accomplish its work, binding variable
 names to a reference to boolean (the same reference used in the abstract
 syntax tree). When processing a variable declaraction, for instance, it
 inserts the variable name into the symbol table, binding it to its
 escaping field. When processing an expression which is a simple
 variable, if the variable occurs in a nested function, its binding in
 the symbol table is set to true. This reflects directly in the abstract
 syntax tree of the variable declaration, as the escape field in the
 variable declaration and the binding in the symbol table are the same
 reference to bool.

Idea of pure algorithm:

 1) Update the symbol table itself, that is: instead of using

   (a) Map Symbol (IORef Bool)

use

   (b) Map Symbol Bool.

This doesn't change the complexity of the algorithm as
searching and updating have the same complexity for many data
structures (maps and hashtables, for example).

In reality, you don't need to use a Map at all.  Just use

   (c) Set Symbol

and symbols not in the set do not escape.  Using (a) gives
you O(n log k) for this step, where n is the size of the AST
and k is the number of symbols.  On the other hand, (c) gives
you O(n log e), where e is the number of escaping symbols.

 2) After doing the whole analysis, use a function
'addEscapeInfo' to process the whole pure AST again adding
information about escaped symbols.  This is O(n log e) as
well.

 The second option is more elegant in my point of view, but would be much
 less efficient than the first one.

While O(n log e) is better than O(n log k), probably the
constants in the pure algorithm are higher than their impure
counterparts.  I guess you could also try to write:

  1) Take an 'AST e' into 'AST (STRef s Bool, e)' in O(n).

  2) Use the impure algorithm inside ST monad in O(n log k).

  3) Take 'AST (STRef s Bool, e)' into 'AST (Bool, e)' in O(n).

  4) 'runST' on the above steps to get a pure function from
 'AST e' into 'AST (Bool, e)'.

The ST monad has the same runtime overhead as IO.  Steps 1) and
3) are used to hide the ST monad from the rest of the compiler.


Cheers,

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


Re: [Haskell-cafe] Minix

2010-06-22 Thread Felipe Lessa
On Tue, Jun 22, 2010 at 08:54:26PM +0200, Henk-Jan van Tuyl wrote:
 I just read about Minix and found a discussion [1] about Andrew
 Tanenbaum (the creator of Minix) wanting to try drivers written in
 Haskell on Minix. It has been four years since, is there currently a
 way to (cross)compile Haskell programs for Minix?

I guess you should look at JHC, it shouldn't be a huge effort to
port it to the Minix 3 OS.

Cheers,

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


  1   2   3   4   >