Re: [Haskell-cafe] Derving NFData via Generics from a type that has a vector doesn't work. (was trying to understand out of memory exceptions)

2013-04-17 Thread anatoly yakovenko
Thanks,  So now i at least get a compiler error

No instance for (NFData (V.Vector Double))

So how would one define NFData instance for vector?


On Apr 16, 2013, at 10:51 PM, Andres Löh and...@well-typed.com wrote:

 NFData Simple where rnf = genericRnf


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


Re: [Haskell-cafe] Derving NFData via Generics from a type that has a vector doesn't work. (was trying to understand out of memory exceptions)

2013-04-17 Thread anatoly yakovenko
so this one works


instance NFData (V.Vector a) where rnf a = force a `seq` ()


any reason why something like this isn't part of the vector library?


Thanks,
Anatoly


On Apr 17, 2013, at 7:51 AM, anatoly yakovenko aeyakove...@gmail.com wrote:

 Thanks,  So now i at least get a compiler error
 
No instance for (NFData (V.Vector Double))
 
 So how would one define NFData instance for vector?
 
 
 On Apr 16, 2013, at 10:51 PM, Andres Löh and...@well-typed.com wrote:
 
 NFData Simple where rnf = genericRnf
 


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


Re: [Haskell-cafe] Derving NFData via Generics from a type that has a vector doesn't work. (was trying to understand out of memory exceptions)

2013-04-17 Thread anatoly yakovenko

On Apr 17, 2013, at 8:05 AM, Andres Löh and...@well-typed.com wrote:

 Changes in version 0.10
 
   *  NFData instances
 


thanks :).

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


[Haskell-cafe] how do i get cabal to reinstall dependencies with profiling enabled?

2013-04-17 Thread Anatoly Yakovenko

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


[Haskell-cafe] trying to understand out of memory exceptions

2013-04-16 Thread Anatoly Yakovenko
-- So why does this code run out of memory?

import Control.DeepSeq
import System.IO
import qualified Data.ByteString.Char8 as BS

scanl' :: NFData a = (a - b - a) - a - [b] - [a]
scanl' f q ls =  q : (case ls of
[]   - []
x:xs - let q' = f q x
in q' `deepseq` scanl' f q' xs)


main = do
   file - openBinaryFile /dev/zero ReadMode
   chars - BS.hGetContents file
   let rv = drop 1000 $ scanl' (+) 0 $ map fromEnum $ BS.unpack
chars
   print (head rv)

-- my scanl' implementation seems to do the right thing, because

main = print $ last $ scanl' (+) (0::Int) [0..]

-- runs without blowing up.  so am i creating a some thunk here?  or is
hGetContents storing values?  any way to get the exception handler to print
a trace of what caused the allocation?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] trying to understand out of memory exceptions

2013-04-16 Thread Anatoly Yakovenko
unfortunately read file tries to get the file size

readFile :: FilePath - IO ByteStringreadFile f = bracket (openFile f
ReadMode) hClose(\h - hFileSize h = hGet h . fromIntegral)


which wont work on a special file, like a socket.  which is what i am
trying to simulate here.



On Tue, Apr 16, 2013 at 11:28 AM, Clark Gaebel cg.wowus...@gmail.comwrote:

 See the comment for hGetContents:

 This function reads chunks at a time, doubling the chunksize on each
 read. The final buffer is then realloced to the appropriate size. For files
  half of available memory, this may lead to memory exhaustion. Consider
 using 
 readFilehttp://hackage.haskell.org/packages/archive/bytestring/0.9.2.1/doc/html/Data-ByteString.html#v:readFile
  in
 this case.


 http://hackage.haskell.org/packages/archive/bytestring/0.9.2.1/doc/html/Data-ByteString-Char8.html#g:31

 Maybe try lazy bytestrings?

   - Clark

 On Tuesday, April 16, 2013, Anatoly Yakovenko wrote:

 -- So why does this code run out of memory?

 import Control.DeepSeq
 import System.IO
 import qualified Data.ByteString.Char8 as BS

 scanl' :: NFData a = (a - b - a) - a - [b] - [a]
 scanl' f q ls =  q : (case ls of
 []   - []
 x:xs - let q' = f q x
 in q' `deepseq` scanl' f q' xs)


 main = do
file - openBinaryFile /dev/zero ReadMode
chars - BS.hGetContents file
let rv = drop 1000 $ scanl' (+) 0 $ map fromEnum $ BS.unpack
 chars
print (head rv)

 -- my scanl' implementation seems to do the right thing, because

 main = print $ last $ scanl' (+) (0::Int) [0..]

 -- runs without blowing up.  so am i creating a some thunk here?  or is
 hGetContents storing values?  any way to get the exception handler to print
 a trace of what caused the allocation?


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


Re: [Haskell-cafe] trying to understand out of memory exceptions

2013-04-16 Thread Anatoly Yakovenko
ah, doh, my mistake.  i accidently pulled in Strict version of bytestring.
 the Lazy works file :).  I have a much more complex program that isn't
working correctly which i was trying to simplify and looks like i added an
error :)


On Tue, Apr 16, 2013 at 11:29 AM, Clark Gaebel cgae...@uwaterloo.ca wrote:

 See the comment for hGetContents:

 This function reads chunks at a time, doubling the chunksize on each
 read. The final buffer is then realloced to the appropriate size. For files
  half of available memory, this may lead to memory exhaustion. Consider
 using 
 readFilehttp://hackage.haskell.org/packages/archive/bytestring/0.9.2.1/doc/html/Data-ByteString.html#v:readFile
  in
 this case.


 http://hackage.haskell.org/packages/archive/bytestring/0.9.2.1/doc/html/Data-ByteString-Char8.html#g:31

 Maybe try lazy bytestrings?

   - Clark

 On Tuesday, April 16, 2013, Anatoly Yakovenko wrote:

 -- So why does this code run out of memory?

 import Control.DeepSeq
 import System.IO
 import qualified Data.ByteString.Char8 as BS

 scanl' :: NFData a = (a - b - a) - a - [b] - [a]
 scanl' f q ls =  q : (case ls of
 []   - []
 x:xs - let q' = f q x
 in q' `deepseq` scanl' f q' xs)


 main = do
file - openBinaryFile /dev/zero ReadMode
chars - BS.hGetContents file
let rv = drop 1000 $ scanl' (+) 0 $ map fromEnum $ BS.unpack
 chars
print (head rv)

 -- my scanl' implementation seems to do the right thing, because

 main = print $ last $ scanl' (+) (0::Int) [0..]

 -- runs without blowing up.  so am i creating a some thunk here?  or is
 hGetContents storing values?  any way to get the exception handler to print
 a trace of what caused the allocation?


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


[Haskell-cafe] Derving NFData via Generics from a type that has a vector doesn't work. (was trying to understand out of memory exceptions)

2013-04-16 Thread Anatoly Yakovenko
-- ok, something in deriving NFData using Generics in a type that has a
Vector in it.


{-# LANGUAGE DeriveGeneric #-}
import Control.DeepSeq
import System.IO
import GHC.Generics (Generic)
import qualified Data.Vector as V
import qualified Data.ByteString.Lazy.Char8 as BL

scanl' :: NFData a = (a - b - a) - a - [b] - [a]
scanl' f q ls =  q : (case ls of
[]   - []
x:xs - let q' = f q x
in q' `deepseq` scanl' f q' xs)

-- this runs without blowing up
-- main = print $ last $ scanl' (+) (0::Int) [0..]

data Simple = Simple (V.Vector Double)
deriving (Show, Generic)

instance NFData Simple

--this blows up
main = do
   let initial = Simple $ V.fromList (take 100 $ repeat 0)
   sumvs (Simple a) (Simple b) = Simple $ V.zipWith (+) a b
   print $ last $ scanl' sumvs initial $ repeat $ initial
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Derving NFData via Generics from a type that has a vector doesn't work. (was trying to understand out of memory exceptions)

2013-04-16 Thread anatoly yakovenko
This compiles but the process runs out of memory, so it seams that NFData 
derivation isn't doing its job.


On Apr 16, 2013, at 12:15 PM, José Pedro Magalhães j...@cs.uu.nl wrote:

 What is the error that you get?
 
 
 Cheers,
 Pedro
 
 On Tue, Apr 16, 2013 at 8:07 PM, Anatoly Yakovenko aeyakove...@gmail.com 
 wrote:
 -- ok, something in deriving NFData using Generics in a type that has a 
 Vector in it.
 
 
 {-# LANGUAGE DeriveGeneric #-}
 import Control.DeepSeq
 import System.IO
 import GHC.Generics (Generic)
 import qualified Data.Vector as V
 import qualified Data.ByteString.Lazy.Char8 as BL
 
 scanl' :: NFData a = (a - b - a) - a - [b] - [a]
 scanl' f q ls =  q : (case ls of
 []   - []
 x:xs - let q' = f q x
 in q' `deepseq` scanl' f q' xs)
 
 -- this runs without blowing up
 -- main = print $ last $ scanl' (+) (0::Int) [0..]
 
 data Simple = Simple (V.Vector Double)
 deriving (Show, Generic)
 
 instance NFData Simple
 
 --this blows up
 main = do
let initial = Simple $ V.fromList (take 100 $ repeat 0)
sumvs (Simple a) (Simple b) = Simple $ V.zipWith (+) a b
print $ last $ scanl' sumvs initial $ repeat $ initial
 
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 


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


Re: [Haskell-cafe] Derving NFData via Generics from a type that has a vector doesn't work. (was trying to understand out of memory exceptions)

2013-04-16 Thread Anatoly Yakovenko
-- + Roman,

-- hey Roman,

-- seems like i cant use deepseq or Generic derive of NFData on data types
containing vectors.  The following code tries to use deepseq to force
evaluation of a type containing vectors, but when the code is running it
seems to not work as expected (blows up in memory).  any ideas?


{-# LANGUAGE DeriveGeneric #-}
import Control.DeepSeq
import System.IO
import GHC.Generics (Generic)
import qualified Data.Vector as V
import qualified Data.ByteString.Lazy.Char8 as BL

scanl' :: NFData a = (a - b - a) - a - [b] - [a]
scanl' f q ls =  q : (case ls of
[]   - []
x:xs - let q' = f q x
in q' `deepseq` scanl' f q' xs)

-- this runs without blowing up
-- main = print $ last $ scanl' (+) (0::Int) [0..]

data Simple = Simple (V.Vector Double)
deriving (Show, Generic)

instance NFData Simple

--this blows up
main = do
   let initial = Simple $ V.fromList (take 100 $ repeat 0)
   sumvs (Simple a) (Simple b) = Simple $ V.zipWith (+) a b
   print $ last $ scanl' sumvs initial $ repeat $ initial




On Tue, Apr 16, 2013 at 12:36 PM, anatoly yakovenko
aeyakove...@gmail.comwrote:

 This compiles but the process runs out of memory, so it seams that NFData
 derivation isn't doing its job.


 On Apr 16, 2013, at 12:15 PM, José Pedro Magalhães j...@cs.uu.nl wrote:

  What is the error that you get?
 
 
  Cheers,
  Pedro
 
  On Tue, Apr 16, 2013 at 8:07 PM, Anatoly Yakovenko 
 aeyakove...@gmail.com wrote:
  -- ok, something in deriving NFData using Generics in a type that has a
 Vector in it.
 
 
  {-# LANGUAGE DeriveGeneric #-}
  import Control.DeepSeq
  import System.IO
  import GHC.Generics (Generic)
  import qualified Data.Vector as V
  import qualified Data.ByteString.Lazy.Char8 as BL
 
  scanl' :: NFData a = (a - b - a) - a - [b] - [a]
  scanl' f q ls =  q : (case ls of
  []   - []
  x:xs - let q' = f q x
  in q' `deepseq` scanl' f q' xs)
 
  -- this runs without blowing up
  -- main = print $ last $ scanl' (+) (0::Int) [0..]
 
  data Simple = Simple (V.Vector Double)
  deriving (Show, Generic)
 
  instance NFData Simple
 
  --this blows up
  main = do
 let initial = Simple $ V.fromList (take 100 $ repeat 0)
 sumvs (Simple a) (Simple b) = Simple $ V.zipWith (+) a b
 print $ last $ scanl' sumvs initial $ repeat $ initial
 
 
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 


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


[Haskell-cafe] anyone else driven mad by trying to setup a gmp free version of haskell platform?

2012-05-08 Thread Anatoly Yakovenko
i would really like to be able to ship haskell based linux binaries,
but the gmp dependency makes it virtually impossible.  so what version
of host os, host ghc, and haskell-platform sources are known to build
a working compiler?

any reason why the dependency on gmp is static?  are the interfaces
between versions actually different?  or can we build a version fo the
compiler that loads the library via dlopen on demand?

Thanks,
Anatoly

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


Re: [Haskell-cafe] acid state

2011-12-13 Thread Anatoly Yakovenko
Ah, i think i get it.

On Tue, Dec 13, 2011 at 12:48 AM, Felipe Almeida Lessa
felipe.le...@gmail.com wrote:
 On Tue, Dec 13, 2011 at 4:55 AM, Anatoly Yakovenko
 aeyakove...@gmail.com wrote:
 So I am trying to understand how acid state works.  The HelloWorld
 example has a

 type Message = String
 data Database = Database [Message]

 $(deriveSafeCopy 0 'base ''Database)

 -- Transactions are defined to run in either the 'Update' monad
 -- or the 'Query' monad.
 addMessage :: Message - Update Database ()
 addMessage msg
    = do Database messages - get
         put $ Database (msg:messages)


 It seems to me that since the Dababase is a list of messages every
 update would require acid-state to rewrite the list into the file, so
 each update would get slower as the list gets bigger, but what I am
 seeing is that updates are constant time regardless of the size of the
 list.  So how does it work?

 acid-state doesn't write the whole thing to the disk every time
 there's a transaction.  Instead, it just writes the transaction on a
 transaction log.  So it will just write something like AddMessage
 msg to the disk.  Periodically, checkpoints are created which *do*
 have all your data inside them (but even so, checkpoints are written
 asynchronously).

 Cheers,

 --
 Felipe.

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


[Haskell-cafe] acid state

2011-12-12 Thread Anatoly Yakovenko
So I am trying to understand how acid state works.  The HelloWorld
example has a

type Message = String
data Database = Database [Message]

$(deriveSafeCopy 0 'base ''Database)

-- Transactions are defined to run in either the 'Update' monad
-- or the 'Query' monad.
addMessage :: Message - Update Database ()
addMessage msg
= do Database messages - get
 put $ Database (msg:messages)


It seems to me that since the Dababase is a list of messages every
update would require acid-state to rewrite the list into the file, so
each update would get slower as the list gets bigger, but what I am
seeing is that updates are constant time regardless of the size of the
list.  So how does it work?

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


[Haskell-cafe] how do i resolve these screwy cabal errors

2010-11-15 Thread Anatoly Yakovenko
package derive-2.3.0.2-ad85bd58710fede3f840a467e84c403e is unusable
due to missing or recursive dependencies:
  haskell-src-exts-1.9.4-e0f8c55bea9fc97376aa3598dfdca6d6
package derive-2.4.1-415d44d2f93198aab5dff67866c17b64 is unusable due
to missing or recursive dependencies:
  haskell-src-exts-1.9.4-e0f8c55bea9fc97376aa3598dfdca6d6


what does that mean?  i reinstalled haskell-src-exts and derive,
doesn't seem to make any difference

Linking dist/build/derive/derive ...
Installing library in /home/anatolyy/.cabal/lib/derive-2.4.1/ghc-6.12.3
Installing executable(s) in /home/anatolyy/.cabal/bin
Registering derive-2.4.1...

/home/anatolyy/.cabal/lib/haskell-src-exts-1.9.4/ghc-6.12.3
Registering haskell-src-exts-1.9.4...

so i cant import Data.DeriveTH
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: how do i resolve these screwy cabal errors

2010-11-15 Thread Anatoly Yakovenko
i reinstalled cabal and reinstalled derive package and that fixed it.

On Sun, Nov 14, 2010 at 1:40 AM, Anatoly Yakovenko
aeyakove...@gmail.com wrote:
 package derive-2.3.0.2-ad85bd58710fede3f840a467e84c403e is unusable
 due to missing or recursive dependencies:
  haskell-src-exts-1.9.4-e0f8c55bea9fc97376aa3598dfdca6d6
 package derive-2.4.1-415d44d2f93198aab5dff67866c17b64 is unusable due
 to missing or recursive dependencies:
  haskell-src-exts-1.9.4-e0f8c55bea9fc97376aa3598dfdca6d6


 what does that mean?  i reinstalled haskell-src-exts and derive,
 doesn't seem to make any difference

 Linking dist/build/derive/derive ...
 Installing library in /home/anatolyy/.cabal/lib/derive-2.4.1/ghc-6.12.3
 Installing executable(s) in /home/anatolyy/.cabal/bin
 Registering derive-2.4.1...

 /home/anatolyy/.cabal/lib/haskell-src-exts-1.9.4/ghc-6.12.3
 Registering haskell-src-exts-1.9.4...

 so i cant import Data.DeriveTH

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


[Haskell-cafe] data.time.zoneinfo

2010-10-20 Thread Anatoly Yakovenko
I am trying to figure out how to use this library, seems like this should work


Prelude Data.Time.ZoneInfo ctx - newContext Nothing
Prelude Data.Time.ZoneInfo name - zoneInfoName (utcOlsonZone ctx) True
Prelude Data.Time.ZoneInfo newOlsonZone ctx name
*** Exception: Data.Time.ZoneInfo.newOlsonZone: invalid argument
(Invalid argument)


but it doesn't, neither does


Prelude Data.Time.ZoneInfo newOlsonZone ctx America/New_York
*** Exception: Data.Time.ZoneInfo.newOlsonZone: invalid argument
(Invalid argument)


and my zoneinfo seems to be kosher on my machine


$ ls /usr/share/zoneinfo/America/New_York
/usr/share/zoneinfo/America/New_York


$ ls /usr/share/zoneinfo/GMT
/usr/share/zoneinfo/GMT


what am i missing?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: data.time.zoneinfo

2010-10-20 Thread Anatoly Yakovenko
passing a full path seems to work, despite the fact that the documentation says

newContext :: Maybe String - IO ContextSource

Create a Context object. A path to the zone-info database may be
specified. Otherwise, the TZDIR environment variable, or a reasonable
default, will be used. An IOError will be thrown on failure.



On Wed, Oct 20, 2010 at 10:40 PM, Anatoly Yakovenko
aeyakove...@gmail.com wrote:
 I am trying to figure out how to use this library, seems like this should work


 Prelude Data.Time.ZoneInfo ctx - newContext Nothing
 Prelude Data.Time.ZoneInfo name - zoneInfoName (utcOlsonZone ctx) True
 Prelude Data.Time.ZoneInfo newOlsonZone ctx name
 *** Exception: Data.Time.ZoneInfo.newOlsonZone: invalid argument
 (Invalid argument)


 but it doesn't, neither does


 Prelude Data.Time.ZoneInfo newOlsonZone ctx America/New_York
 *** Exception: Data.Time.ZoneInfo.newOlsonZone: invalid argument
 (Invalid argument)


 and my zoneinfo seems to be kosher on my machine


 $ ls /usr/share/zoneinfo/America/New_York
 /usr/share/zoneinfo/America/New_York


 $ ls /usr/share/zoneinfo/GMT
 /usr/share/zoneinfo/GMT


 what am i missing?

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


Re: [Haskell-cafe] Exception: : changeWorkingDirectory: does not exist (No such file or directory)

2010-05-25 Thread Anatoly Yakovenko
there must have been some linker incompatibility.  gentoo must have
updated some library that ghci depended on causing this breakage.  I
re-installed ghc and everything started working.

On Mon, May 24, 2010 at 1:19 PM, Daniel Fischer
daniel.is.fisc...@web.de wrote:
 On Monday 24 May 2010 21:35:10, Anatoly Yakovenko wrote:
 :set -fglasgow-exts

 Can't you be more discriminating and turn on only those extensions you
 regularly use?

 :set prompt  

 Thats all i have in my .ghci file

 Shouldn't cause a cd.

 Maybe

 $ ghci -v4

 would give a hint?

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


Re: [Haskell-cafe] Exception: : changeWorkingDirectory: does not exist (No such file or directory)

2010-05-24 Thread Anatoly Yakovenko
:set -fglasgow-exts
:set prompt  

Thats all i have in my .ghci file

On Fri, May 21, 2010 at 12:14 PM, Daniel Fischer
daniel.is.fisc...@web.de wrote:
 On Friday 21 May 2010 20:50:39, Anatoly Yakovenko wrote:
 anyone else seeing this behavior?

 anato...@anatolyy-linux ~ $ ghci
 GHCi, version 6.12.1: 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.

  1/2

 0.5
 *** Exception: : changeWorkingDirectory: does not exist (No such file
 or directory)

  1/2

 *** Exception: : changeWorkingDirectory: does not exist (No such file
 or directory)

 Never seen that.
 Just to make sure, there's nothing in any of your .ghci files that might
 cause it?

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


[Haskell-cafe] Exception: : changeWorkingDirectory: does not exist (No such file or directory)

2010-05-21 Thread Anatoly Yakovenko
anyone else seeing this behavior?

anato...@anatolyy-linux ~ $ ghci
GHCi, version 6.12.1: 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.
 1/2
0.5
*** Exception: : changeWorkingDirectory: does not exist (No such file
or directory)
 1/2
*** Exception: : changeWorkingDirectory: does not exist (No such file
or directory)

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


Re: [Haskell-cafe] pandoc code bocks not working

2010-02-16 Thread Anatoly Yakovenko
Thanks, that solved it.

I am also seening that pandoc compiled with 6.12 seems to barf on the
.css file that is used in the examples.


commitAndReleaseBuffer: invalid argument (Invalid or incomplete
multibyte or wide character)


On Sun, Feb 14, 2010 at 5:48 PM, Walter De Jonge w...@skynet.be wrote:
 http://johnmacfarlane.net/pandoc/README.html#delimited-code-blocks

 Like regular code blocks, delimited code blocks must be separated from
 surrounding text by blank lines.

 goodluck

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

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


[Haskell-cafe] pandoc code bocks not working

2010-02-14 Thread Anatoly Yakovenko
i am getting these failures with pandoc, or maybe i am not using
markdown correctly


1. hello world
~
code block failed
~
* hello world
~
code block failed
~
* hello world
   clode block failed

hello world
===
~
code block ok
~
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] hipmunkplayground on windows

2009-11-17 Thread Anatoly Yakovenko
Anyone else seeing a bunch of linker errors when trying to install
HipmunkPlayground?

this is what i see:

C:\Program 
Files\Haskell\OpenGL-2.2.3.0\ghc-6.10.4/libHSOpenGL-2.2.3.0.a(RenderMode.o):fake:(.text+0x5be):
more undefined references to `glRenderMode' follow
C:\Program 
Files\Haskell\OpenGL-2.2.3.0\ghc-6.10.4/libHSOpenGL-2.2.3.0.a(Environments.o):fake:(.text+0x1c25):
undefined reference to `glGetTexEnvfv'
C:\Program 
Files\Haskell\OpenGL-2.2.3.0\ghc-6.10.4/libHSOpenGL-2.2.3.0.a(Environments.o):fake:(.text+0x5779):
undefined reference to `glTexEnvi'
C:\Program 
Files\Haskell\OpenGL-2.2.3.0\ghc-6.10.4/libHSOpenGL-2.2.3.0.a(Environments.o):fake:(.text+0x58f5):
undefined reference to `glGetTexEnviv'
C:\Program 
Files\Haskell\OpenGL-2.2.3.0\ghc-6.10.4/libHSOpenGL-2.2.3.0.a(Environments.o):fake:(.text+0x5aba):
undefined reference to `glTexEnvf'
C:\Program 
Files\Haskell\OpenGL-2.2.3.0\ghc-6.10.4/libHSOpenGL-2.2.3.0.a(Environments.o):fake:(.text+0x5c7d):
undefined reference to `glGetTexEnvfv'
C:\Program 
Files\Haskell\OpenGL-2.2.3.0\ghc-6.10.4/libHSOpenGL-2.2.3.0.a(Environments.o):fake:(.text+0x6d51):
undefined reference to `glTexEnvfv'
C:\Program 
Files\Haskell\OpenGL-2.2.3.0\ghc-6.10.4/libHSOpenGL-2.2.3.0.a(Queries.o):fake:(.text+0x339):
undefined reference to `glGetTexLevelParameteriv'
collect2: ld returned 1 exit status
cabal.exe: Error: some packages failed to install:
HipmunkPlayground-5.0.0 failed during the building phase. The exception was:
exit: ExitFailure 1
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: a boring parser

2009-10-01 Thread Anatoly Yakovenko
so whats pretty cool is that I can traverse arbitrary data structures as  well:

data Tree a = Tree (Tree a) a (Tree a) | Bottom
deriving Show

left a = do
   make $ \ st - do
  case(st) of
 (Bottom) - eos
 (Tree left val right) -
case (a  val) of
   True - return $ (val, left)
   False - noMatch

right a = do
   make $ \ st - do
  case(st) of
 (Bottom) - eos
 (Tree left val right) -
case (a  val) of
   True - return $ (val, right)
   False - noMatch

eqT a = do
   make $ \ st - do
  case(st) of
 (Bottom) - eos
 (Tree _ val _) -
case (a == val) of
   True - return $ (val, st)
   False - noMatch

search a = manyTill (left a | right a) (eqT a)

 run (search 5) $ Tree (Tree Bottom 1 Bottom) 3 (Tree Bottom 5 Bottom)
Right (([3],5),Tree Bottom 5 Bottom)



On Wed, Sep 30, 2009 at 8:04 PM, Anatoly Yakovenko
aeyakove...@gmail.com wrote:
 i got annoyed with Parsec and wrote a much more boring parser which
 allows me to parse anything with any kind of matching i want.  Its
 basically a combination of State and Error monads.

 So i can use a grep like parser that matches via a regular expression
 over a list of lines

 grep re = do
   vv::B.ByteString - any
   let (_,_,_,rv) = (vv =~
 re)::(B.ByteString,B.ByteString,B.ByteString,[B.ByteString])
   case (rv) of
      [] - throwError no match
      _ - return $ rv

 run (grep $ C.pack (hello)) $ [C.pack hello world]
 Right ([hello],[])

 or use the same library to scan over a string by combining regular expressions

 regex re = do
   make $ \ st - do
      case (B.null st) of
         True - throwError eos
         _ - do
            let (_,_,after,rv) = (st =~
 re)::(B.ByteString,B.ByteString,B.ByteString,[B.ByteString])
            case (rv) of
               [] - throwError no match
               _ - return $ (rv,after)



  run (do aa - regex $ C.pack (hello); bb - regex $ C.pack  (world); 
 return (aa,bb) ) $ C.pack hello world
 Right (([hello],[world]),)

 or simply match integers in a list, or anything that is of type Eq

 run (many1 $ eq 1) [1,1,1,2,3,4]
 Right ([1,1,1],[2,3,4])

 i can define lt

 lt cc = do
   vv - any
   case (vv  cc) of
      True - return $ vv
      _ - throwError no match

 and do

 run (many1 $ lt 5 | eq 5) [1..10]
 Right ([1,2,3,4,5],[6,7,8,9,10])

 here is the implementation

 module Parser( ParserM     --type alias for the parser ParserM a b is
 over stream a and returns b
             , make        --makes a parser from a matching function of
 type :: stream - m (match_data,stream)
                           --for example any is implemented via:
                           --any :: ParserM [a] a
                           --any = make $ \ ll -
                           --   case (ll) of
                           --         (hh:tt) - return $ (hh,tt)
                           --               _ - throwError eos
                           --matches and returns an element from a
 list, which makes any of type :: ParserM [a] a
             , any         --matches any element from [a] type stream
             , eq          --matches an equal element from [Eq] stream,
 trivialy implemented in terms of any
                           --eq :: Eq a = a - ParserM [a] a
                           --eq cc = do
                           --   vv - any
                           --   case (vv == cc) of
                           --      True - return $ vv
                           --         _ - throwError no match
             , (|)       --or operator, tries the left one then the right one
             , manyTill    --collects the results of parser 1 until
 parser 2 succeeds
             , many1       --collects the results of the parser, must
 succeed at least once
             , many        --collects the results of a parser
             , run         --runs the parser
             ) where

 import Control.Monad.State.Lazy
 import Control.Monad.Error
 import Test.QuickCheck
 import Control.Monad.Identity
 import Prelude hiding (any)

 type ParserM a c = StateT a (ErrorT [Char] Identity) c

 make pp = do
   st - get
   (rv,nst) - pp $ st
   put $ nst
   return $ rv

 aa | bb = aa `catchError` \ _ - bb

 manyTill :: ParserM a c - ParserM a d - ParserM a ([c],d)
 manyTill pp ee = do
   do dd - ee
      return $ ([],dd)
   `catchError` \ _ - do
      cc - pp
      (ccs,dd) - manyTill pp ee
      return $ (cc:ccs,dd)

 many1 pp = do
   rv - pp
   rest - many1 pp `catchError` \ _ - return $ []
   return $ rv : rest

 many pp = do many1 pp
         | return []


 any :: ParserM [a] a
 any = make $ \ ll -
   case (ll) of
      (hh:tt) - return $ (hh,tt)
      _ - throwError eos

 eq :: Eq a = a - ParserM [a] a
 eq cc = do
   vv - any
   case (vv == cc) of
      True - return $ vv
      _ - throwError no match

 lt cc = do
   vv - any
   case (vv  cc) of
      True

[Haskell-cafe] a boring parser

2009-09-30 Thread Anatoly Yakovenko
i got annoyed with Parsec and wrote a much more boring parser which
allows me to parse anything with any kind of matching i want.  Its
basically a combination of State and Error monads.

So i can use a grep like parser that matches via a regular expression
over a list of lines

grep re = do
  vv::B.ByteString - any
  let (_,_,_,rv) = (vv =~
re)::(B.ByteString,B.ByteString,B.ByteString,[B.ByteString])
  case (rv) of
     [] - throwError no match
     _ - return $ rv

 run (grep $ C.pack (hello)) $ [C.pack hello world]
Right ([hello],[])

or use the same library to scan over a string by combining regular expressions

regex re = do
  make $ \ st - do
     case (B.null st) of
        True - throwError eos
        _ - do
           let (_,_,after,rv) = (st =~
re)::(B.ByteString,B.ByteString,B.ByteString,[B.ByteString])
           case (rv) of
              [] - throwError no match
              _ - return $ (rv,after)



  run (do aa - regex $ C.pack (hello); bb - regex $ C.pack  (world); 
 return (aa,bb) ) $ C.pack hello world
Right (([hello],[world]),)

or simply match integers in a list, or anything that is of type Eq

 run (many1 $ eq 1) [1,1,1,2,3,4]
Right ([1,1,1],[2,3,4])

i can define lt

lt cc = do
  vv - any
  case (vv  cc) of
     True - return $ vv
     _ - throwError no match

and do

 run (many1 $ lt 5 | eq 5) [1..10]
Right ([1,2,3,4,5],[6,7,8,9,10])

here is the implementation

module Parser( ParserM     --type alias for the parser ParserM a b is
over stream a and returns b
            , make        --makes a parser from a matching function of
type :: stream - m (match_data,stream)
                          --for example any is implemented via:
                          --any :: ParserM [a] a
                          --any = make $ \ ll -
                          --   case (ll) of
                          --         (hh:tt) - return $ (hh,tt)
                          --               _ - throwError eos
                          --matches and returns an element from a
list, which makes any of type :: ParserM [a] a
            , any         --matches any element from [a] type stream
            , eq          --matches an equal element from [Eq] stream,
trivialy implemented in terms of any
                          --eq :: Eq a = a - ParserM [a] a
                          --eq cc = do
                          --   vv - any
                          --   case (vv == cc) of
                          --      True - return $ vv
                          --         _ - throwError no match
            , (|)       --or operator, tries the left one then the right one
            , manyTill    --collects the results of parser 1 until
parser 2 succeeds
            , many1       --collects the results of the parser, must
succeed at least once
            , many        --collects the results of a parser
            , run         --runs the parser
            ) where

import Control.Monad.State.Lazy
import Control.Monad.Error
import Test.QuickCheck
import Control.Monad.Identity
import Prelude hiding (any)

type ParserM a c = StateT a (ErrorT [Char] Identity) c

make pp = do
  st - get
  (rv,nst) - pp $ st
  put $ nst
  return $ rv

aa | bb = aa `catchError` \ _ - bb

manyTill :: ParserM a c - ParserM a d - ParserM a ([c],d)
manyTill pp ee = do
  do dd - ee
     return $ ([],dd)
  `catchError` \ _ - do
     cc - pp
     (ccs,dd) - manyTill pp ee
     return $ (cc:ccs,dd)

many1 pp = do
  rv - pp
  rest - many1 pp `catchError` \ _ - return $ []
  return $ rv : rest

many pp = do many1 pp
        | return []


any :: ParserM [a] a
any = make $ \ ll -
  case (ll) of
     (hh:tt) - return $ (hh,tt)
     _ - throwError eos

eq :: Eq a = a - ParserM [a] a
eq cc = do
  vv - any
  case (vv == cc) of
     True - return $ vv
     _ - throwError no match

lt cc = do
  vv - any
  case (vv  cc) of
     True - return $ vv
     _ - throwError no match

run pp dd = runIdentity $ runErrorT $ runStateT pp dd
run' = flip run


prop_MatchA = (Right ('a',bc)) == (run' abc $ eq 'a')
prop_MatchEOS = (Left eos) == (run'   $ eq 'a')
prop_MatchNoMatch = (Left no match) == (run' (bcd) $ eq 'a')

prop_MatchABC =(Right ('c',))== (run' abc $ do  eq 'a'
                                                   eq 'b'
                                                   eq 'c')

prop_MatchA_C = (run' abc $ do eq 'a'
                                eq 'd' | eq 'b' | any
                                eq 'c') == (Right ('c',))

prop_Or =      (run' abc $ do { eq 'a'
                               ; do     { eq 'b'
                                        ; eq 'd'
                                        }
                                 | do { eq 'b'
                                        ; eq 'c'
                                        }
                               }) == (Right ('c',))

prop_UntilC = (Right ((,'c'),)) == (run' (c) $ manyTill any $ eq 'c')

prop_Until1 ls =
  let rv = run' (ls ++ [1]) $ manyTill any $ eq 1
  in case (rv) of
    

[Haskell-cafe] i am missing something really trivial with parsec

2009-09-29 Thread Anatoly Yakovenko
number = do { num - natural
; return $ num
}
main = do
   txt - hGetContents stdin
   print $ parse number stdin txt


why doesn't that work?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] traversing a tree using monad.cont

2009-05-04 Thread Anatoly Yakovenko
thanks, that looks promising, but will probably take me a week to understand :)

On Sun, May 3, 2009 at 2:40 PM, Ryan Ingram ryani.s...@gmail.com wrote:
 Cont with success and failure isn't Cont; it's something else (albeit similar)

 There's a great exposition of using something much like Cont to get
 success and failure for free here:
 http://www-ps.informatik.uni-kiel.de/~sebf/haskell/barefaced-pilferage-of-monadic-bind.lhs.html

  -- ryan

 On Sat, May 2, 2009 at 2:13 AM, Anatoly Yakovenko aeyakove...@gmail.com 
 wrote:
 Though I don't fully understand what you are doing (specifically what you
 mean by specific order), but in a lazy language, traversals are usually
 simply encoded as lists.  Just write a function which returns all the leaves
 as a list, and filter over it.

 yea, i know, i am trying to learn how to use the Cont monad. or
 continuation in haskell.  The idea is that while i am processing some
 data i may hit a point whree some dependency isn't met and i want to
 take a different branch via continuation.  I expect that branch to
 furfill my dependency and when its done i want to continue down the
 original branch


 module TestCont where
 import Control.Monad.Cont
 import Control.Monad.Identity
 import Control.Monad.State.Lazy

 --our stupid tree
 data Tree a = Tree [Tree a]
            | Leaf a

 --traverse all the branches
 search (Tree ts) next = do
   mapM_ (\ ti - (callCC (search ti))) ts
   next $ ()

 search tt@(Leaf a) next = do
   cur - lift get
   case ((cur + 1) == a) of
      True - do --the current leaf is what we want, update the state and 
 return

 this is where i succeed in my current branch, so i can just do my thing and 
 exit

         lift $ put a
         return $ ()
      False - do --the current leaf is not what we want, continue first, 
 then try again

 this is where i fail, so i want to take the other branch first
 expecting it to fulfill my dependency.

         next ()
         search tt (\ _ - error fail)

 t1 = Leaf 1
 t2 = Leaf 2
 t3 = Tree [t1,t2]
 t4 = Leaf 3
 t5::Tree Int = Tree [t4,t3]

 run =  runIdentity (runStateT ((runContT $ callCC (search t5)) return) 0)


 but i think next doesn't do exactly what i think it does
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


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


Re: [Haskell-cafe] traversing a tree using monad.cont

2009-05-02 Thread Anatoly Yakovenko
 Though I don't fully understand what you are doing (specifically what you
 mean by specific order), but in a lazy language, traversals are usually
 simply encoded as lists.  Just write a function which returns all the leaves
 as a list, and filter over it.

yea, i know, i am trying to learn how to use the Cont monad. or
continuation in haskell.  The idea is that while i am processing some
data i may hit a point whree some dependency isn't met and i want to
take a different branch via continuation.  I expect that branch to
furfill my dependency and when its done i want to continue down the
original branch


 module TestCont where
 import Control.Monad.Cont
 import Control.Monad.Identity
 import Control.Monad.State.Lazy

 --our stupid tree
 data Tree a = Tree [Tree a]
            | Leaf a

 --traverse all the branches
 search (Tree ts) next = do
   mapM_ (\ ti - (callCC (search ti))) ts
   next $ ()

 search tt@(Leaf a) next = do
   cur - lift get
   case ((cur + 1) == a) of
      True - do --the current leaf is what we want, update the state and 
 return

this is where i succeed in my current branch, so i can just do my thing and exit

         lift $ put a
         return $ ()
      False - do --the current leaf is not what we want, continue first, 
 then try again

this is where i fail, so i want to take the other branch first
expecting it to fulfill my dependency.

         next ()
         search tt (\ _ - error fail)

 t1 = Leaf 1
 t2 = Leaf 2
 t3 = Tree [t1,t2]
 t4 = Leaf 3
 t5::Tree Int = Tree [t4,t3]

 run =  runIdentity (runStateT ((runContT $ callCC (search t5)) return) 0)


but i think next doesn't do exactly what i think it does
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] traversing a tree using monad.cont

2009-05-02 Thread Anatoly Yakovenko
its a syntax tree, and at some point i hit a type reference who'se
declaration will be satisfied in some other part of the tree.  the
type references are always leaves, so when i hit a typeref, i just
want to continue along the rest of the parser until i hit a
declaration.  My current solution is to do multiple passes, store the
declarations in a map in one pass then resolve all the type references
in another, but that's kind of boring.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] traversing a tree using monad.cont

2009-05-01 Thread Anatoly Yakovenko
So I am trying to traverse a tree in a specific order, but i have no
idea where the things that i am looking for are located, and i want to
avoid explicit backtracking.  I was thinking i could do it with the
continuation monad.  Here is what i have

module TestCont where
import Control.Monad.Cont
import Control.Monad.Identity
import Control.Monad.State.Lazy

--our stupid tree
data Tree a = Tree [Tree a]
| Leaf a

--traverse all the branches
search (Tree ts) next = do
   mapM_ (\ ti - (callCC (search ti))) ts
   next $ ()

search tt@(Leaf a) next = do
   cur - lift get
   case ((cur + 1) == a) of
  True - do --the current leaf is what we want, update the state and return
 lift $ put a
 return $ ()
  False - do --the current leaf is not what we want, continue
first, then try again
 next ()
 search tt (\ _ - error fail)

t1 = Leaf 1
t2 = Leaf 2
t3 = Tree [t1,t2]
t4 = Leaf 3
t5::Tree Int = Tree [t4,t3]

run =  runIdentity (runStateT ((runContT $ callCC (search t5)) return) 0)

it seems like next isn't quite doing what i want, because i don't
think I ever try again after i call next $ () in the second clause.
Any ideas?

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


Re: [Haskell-cafe] understanding typeable

2009-04-15 Thread Anatoly Yakovenko
So I am getting a little further, but i am seeing this bizarre behaviour:

I wrote a function that will fold over parameters and push them into a
constructor if it can
given this type:

   data Foo = FooC Int
| BarC Int
deriving (Data, Typeable, Show)

i can do this:

let a::Maybe Foo = foldFunc (Just FooC) (params $ BarC 1)
   Loading package syb ... linking ... done.
a
   Just (FooC 1)

here is the implementation

   data Child = forall a. (Typeable a, Data a) = Child a

   params::(Data a) = a - [Child]
   params = gmapQ Child

   --foldFunc :: (Typeable x, Data y) = (Maybe x) - [Child] - Maybe y
   --foldFunc :: forall y1 y.  (Typeable y1, Data y) = Maybe y1 -
[Child] - Maybe y
   foldFunc (Just ff) (ch:[]) = applyCtor ff ch
   foldFunc (Just ff) (ch:tt) = foldFunc (applyFunc ff ch) tt
   foldFunc Nothing _ = Nothing
   foldFunc (Just ff) [] = castObj ff
  where
 castObj::(Typeable y, Data x) = y - (Maybe x)
 castObj = cast

   applyCtor :: (Typeable x, Data y) = x - Child - Maybe y
   applyCtor ff (Child ch) = do
  func - castFunc ff
  return $ func ch
  where
 castFunc::(Typeable y, Data x, Data z) = y - (Maybe (x - z))
 castFunc = cast

   applyFunc :: (Typeable x, Typeable y) = x - Child - Maybe y
   applyFunc ff (Child ch) = do
  func - castFunc ff
  return $ func ch
  where
 castFunc::(Typeable y, Data x, Typeable z) = y - (Maybe (x - z))
 castFunc = cast

now this is the weird part:

--foldFunc :: (Typeable x, Data y) = (Maybe x) - [Child] - Maybe y
--foldFunc :: forall y1 y.  (Typeable y1, Data y) = Maybe y1 -
[Child] - Maybe y

if i uncomment either one of those, (shouldn't they be equivalent?), i
get an error, the first one gives me

   ParseG.hs:44:39:
   Ambiguous type variable `x' in the constraint:
 `Typeable x'
   arising from a use of `applyFunc' at ParseG.hs:44:39-53
   Probable fix: add a type signature that fixes these type variable(s)
   Failed, modules loaded: none.

the second one gives me:

   ParseG.hs:46:24:
   Could not deduce (Data y1) from the context (Typeable y1, Data y)
 arising from a use of `castObj' at ParseG.hs:46:24-33
   Possible fix:
 add (Data y1) to the context of the type signature for `foldFunc'
   In the expression: castObj ff
   In the definition of `foldFunc':
   foldFunc (Just ff) []
  = castObj ff
  where
  castObj :: (Typeable y, Data x) = y - (Maybe x)
  castObj = cast

   ParseG.hs:46:32:
   Couldn't match expected type `y' against inferred type `y1'
 `y' is a rigid type variable bound by
 the type signature for `foldFunc' at ParseG.hs:42:22
 `y1' is a rigid type variable bound by
  the type signature for `foldFunc' at ParseG.hs:42:19
   In the first argument of `castObj', namely `ff'
   In the expression: castObj ff
   In the definition of `foldFunc':
   foldFunc (Just ff) []
  = castObj ff
  where
  castObj :: (Typeable y, Data x) = y - (Maybe x)
  castObj = cast
   Failed, modules loaded: none.

So they are not equivalent, so why is that so, and why is this the
type signature of the function if i dont give one:

:t foldFunc
   foldFunc :: forall y1 y.
   (Typeable y1, Data y) =
   Maybe y1 - [Child] - Maybe y
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] is there any reason why Language.C.Syntax.AST.CTranslUnit doesn't derive show?

2009-03-27 Thread Anatoly Yakovenko
is there any reason why Language.C.Syntax.AST.CTranslUnit doesn't
derive show?  I would like to look at the data structure it generates.
 It's a lot easier to experiment it when i can write a template C
file, print out the AST and then modify that data structure directly,
instead of trying to grok the library.

Thanks for your great work btw, the parser is pretty sweet.
Anatoly
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: is there any reason why Language.C.Syntax.AST.CTranslUnit doesn't derive show?

2009-03-27 Thread Anatoly Yakovenko
ah, i am guessing its because you can use Data.Generics.gshow to do
the same thing.  Seems like that library will come in handy when
manipulating the AST, pretty cool stuff.

On Fri, Mar 27, 2009 at 5:53 PM, Anatoly Yakovenko
aeyakove...@gmail.com wrote:
 is there any reason why Language.C.Syntax.AST.CTranslUnit doesn't
 derive show?  I would like to look at the data structure it generates.
  It's a lot easier to experiment it when i can write a template C
 file, print out the AST and then modify that data structure directly,
 instead of trying to grok the library.

 Thanks for your great work btw, the parser is pretty sweet.
 Anatoly

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


[Haskell-cafe] is there a version of hsffig that builds on a recent versin of haskell?

2009-03-15 Thread Anatoly Yakovenko
is there a version of hsffig that builds on a recent versin of haskell?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: is there a version of hsffig that builds on a recent versin of haskell?

2009-03-15 Thread Anatoly Yakovenko
i can try to fix it if i can get some help.  i've never used cabal.
any idea why i am getting this:

anato...@anatolyy-linux /shared/anatolyy/hsffig-1.0 $ cabal install
Warning: HSFFIG.cabal: The field hs-source-dir is deprecated, please use
hs-source-dirs
Warning: HSFFIG.cabal: The field hs-source-dir is deprecated, please use
hs-source-dirs
Warning: HSFFIG.cabal: The field hs-source-dir is deprecated, please use
hs-source-dirs
Resolving dependencies...
Configuring HSFFIG-1.0...
configure: searching for ghc in path.
configure: found ghc at /usr/bin/ghc
/usr/bin/ghc --version tmp16646
configure: looking for package tool: ghc-pkg near compiler in /usr/bin/ghc
configure: found package tool in /usr/bin/ghc-pkg
configure: Using install prefix: /shared/anatolyy/.cabal
configure: Using compiler: /usr/bin/ghc
configure: Compiler flavor: GHC
configure: Compiler version: 6.10.1
configure: Using package tool: /usr/bin/ghc-pkg
configure: No haddock found
configure: No happy found
configure: No alex found
configure: Using hsc2hs: /usr/bin/hsc2hs
configure: No cpphs found
configure: Reading installed packages...
/usr/bin/ghc-pkg --user list tmp16646
cannot parse package list
cabal: Error: some packages failed to install:
HSFFIG-1.0 failed during the configure step. The exception was:
exit: ExitFailure 1
anato...@anatolyy-linux /shared/anatolyy/hsffig-1.0 $ /usr/bin/ghc-pkg
--user list
/usr2/anatolyy/.ghc/x86_64-linux-6.10.1/package.conf:
{FiniteMap-0.1}, {HUnit-1.2.0.3}, {X11-1.4.5}, {haskell98-1.0.1.0},
{html-1.0.1.2}, {mtl-1.1.0.2}, {parsec-2.1.0.1}, {process-1.0.1.1},
{regex-base-0.93.1}, {regex-compat-0.92}, {regex-posix-0.94.1},
{text-0.1}, {xmonad-0.8.1}


On Sun, Mar 15, 2009 at 11:20 AM, Dmitry Golubovsky
golubov...@gmail.com wrote:
 On Mar 15, 4:03 am, Anatoly Yakovenko aeyakove...@gmail.com wrote:
 is there a version of hsffig that builds on a recent versin of haskell?
 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

 Unfortunately no. There have been too many changes in GCC and GHC
 since, and too low interest to the project from other developers, so I
 did not maintain it.

 Dmitry.


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


[Haskell-cafe] do nmergeIO or mergeIO preserve order?

2009-03-10 Thread Anatoly Yakovenko
do nmergeIO or mergeIO preserve order? or not preserve order?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] do nmergeIO or mergeIO preserve order?

2009-03-10 Thread Anatoly Yakovenko
Hmm, yea, actually that makes sense.  What i am looking for is
something that maps over a list and returns the list in order which
the values are evaluated.  looks like i can implement that pretty
easily with unamb.

On Tue, Mar 10, 2009 at 2:33 PM, Luke Palmer lrpal...@gmail.com wrote:
 Although it is not formally specified, my intuition for the specification is
 that order is preserved within each of the lists.

 Luke

 On Tue, Mar 10, 2009 at 2:50 PM, Anatoly Yakovenko aeyakove...@gmail.com
 wrote:

 do nmergeIO or mergeIO preserve order? or not preserve order?
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


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


Re: [Haskell-cafe] do nmergeIO or mergeIO preserve order?

2009-03-10 Thread Anatoly Yakovenko
i think this would still force me to evailuate the whole list, right?
i would want something that pipes the results into a channel that i
can lazyly read as the results are available.

On Tue, Mar 10, 2009 at 2:44 PM, Luke Palmer lrpal...@gmail.com wrote:
 I think nmergeIO . map (:[]) should do the trick.

 Luke

 On Tue, Mar 10, 2009 at 3:41 PM, Anatoly Yakovenko aeyakove...@gmail.com
 wrote:

 Hmm, yea, actually that makes sense.  What i am looking for is
 something that maps over a list and returns the list in order which
 the values are evaluated.  looks like i can implement that pretty
 easily with unamb.

 On Tue, Mar 10, 2009 at 2:33 PM, Luke Palmer lrpal...@gmail.com wrote:
  Although it is not formally specified, my intuition for the
  specification is
  that order is preserved within each of the lists.
 
  Luke
 
  On Tue, Mar 10, 2009 at 2:50 PM, Anatoly Yakovenko
  aeyakove...@gmail.com
  wrote:
 
  do nmergeIO or mergeIO preserve order? or not preserve order?
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 


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


Re: [Haskell-cafe] do nmergeIO or mergeIO preserve order?

2009-03-10 Thread Anatoly Yakovenko
 I would also consider it bad style to be fully polymorphic in this case, as
 you require polymorphic seq, which is evil (though I don't have the space to
 argue this right now :-).  Unamb would be bad style, also, since your
 semantics are nondeterministic and so you wouldn't meet the precondition.
 Surely your result would have to be in IO.  (amb would be okay)

what do you mean by fully polymorphic?

 Here is how I would do it:

 chooseIO :: [IO a] - IO [a]
 chooseIO xs = do
     chan - newChan
     let eval io = forkIO (io = writeChan chan)
     forkIO $ mapM_ eval xs
     getChanContents chan

Cool, thanks, thats basically what iw as thinking to.

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


Re: [Haskell-cafe] Re: Haskell on ARM (was Re: ANN: Topkata)

2009-01-30 Thread Anatoly Yakovenko
i don't think haskell on llvm exists, so the answer would be no

On Thu, Jan 29, 2009 at 8:36 AM, Dan Mead d.w.m...@gmail.com wrote:
 does the haskell on llvm compiler support the ghc extentions?

 On Wed, Jan 28, 2009 at 7:27 PM, Anatoly Yakovenko aeyakove...@gmail.com
 wrote:

 ghc llvm port would enable arm support as well.  i know there were
 some issues with llvm when this was discusses a couple of years ago.
 has anyone checked if that's the case?

 On Wed, Jan 28, 2009 at 3:14 PM, Braden Shepherdson
 braden.shepherd...@gmail.com wrote:
  Conrad Meyer wrote:
 
  On Wednesday 28 January 2009 08:15:44 am Braden Shepherdson wrote:
 
  Dan Mead wrote:
 
  has there been any movement on this topic? i'm also interested in
  haskell on arm
 
 
  do you guys thing telling ghc to emit C and then compiling that for
  arm
  is a better route than
  getting direct compilation to work?
 
  If you look on the GHC-on-ARM page[1], you'll find my attempts to
  bootstrap GHC 6.6 (the last version where cross-compiling GHC actually
  worked) to ARM.
 
  The only success I had was in using jhc (not GHC) to generate portable
  C, which cross-compiled and ran fine (on my Nokia N810). GHC's C
  wouldn't compile out of the box, and I'm not sure what libraries or
  other hackery is required to make it do so.
 
  Details of the failed cross-compilation and success with jhc are on
  the
  wiki page[1].
 
  I'd love to have this working, but I have no time at all this term.
 
 
  Braden Shepherdson
  shepheb
 
  Have you considered trying to bootstrap ghc with jhc?
 
  Regards,
 
  Unfortunately this is not possible. The Haskell code in GHC relies on
  some
  GHC-only extensions. jhc can't compile GHC because it doesn't have those
  extensions. jhc can't even compile itself, since it too relies on those
  extensions.
 
 
  Braden Shepherdson
  shepheb
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


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


Re: [Haskell-cafe] Re: Haskell on ARM (was Re: ANN: Topkata)

2009-01-28 Thread Anatoly Yakovenko
ghc llvm port would enable arm support as well.  i know there were
some issues with llvm when this was discusses a couple of years ago.
has anyone checked if that's the case?

On Wed, Jan 28, 2009 at 3:14 PM, Braden Shepherdson
braden.shepherd...@gmail.com wrote:
 Conrad Meyer wrote:

 On Wednesday 28 January 2009 08:15:44 am Braden Shepherdson wrote:

 Dan Mead wrote:

 has there been any movement on this topic? i'm also interested in
 haskell on arm


 do you guys thing telling ghc to emit C and then compiling that for arm
 is a better route than
 getting direct compilation to work?

 If you look on the GHC-on-ARM page[1], you'll find my attempts to
 bootstrap GHC 6.6 (the last version where cross-compiling GHC actually
 worked) to ARM.

 The only success I had was in using jhc (not GHC) to generate portable
 C, which cross-compiled and ran fine (on my Nokia N810). GHC's C
 wouldn't compile out of the box, and I'm not sure what libraries or
 other hackery is required to make it do so.

 Details of the failed cross-compilation and success with jhc are on the
 wiki page[1].

 I'd love to have this working, but I have no time at all this term.


 Braden Shepherdson
 shepheb

 Have you considered trying to bootstrap ghc with jhc?

 Regards,

 Unfortunately this is not possible. The Haskell code in GHC relies on some
 GHC-only extensions. jhc can't compile GHC because it doesn't have those
 extensions. jhc can't even compile itself, since it too relies on those
 extensions.


 Braden Shepherdson
 shepheb

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

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


[Haskell-cafe] is there something special about the Num instance?

2008-12-03 Thread Anatoly Yakovenko
module Test where
--why does this work:
data Test = Test

class Foo t where
   foo :: Num v = t - v - IO ()

instance Foo Test where
   foo _ 1 = print $ one
   foo _ _ = print $ not one

--but this doesn't?

class Bar t where
   bar :: Foo v = t - v - IO ()

instance Bar Test where
   bar _ Test = print $ test
   bar _ _ = print $ not test
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] is there something special about the Num instance?

2008-12-03 Thread Anatoly Yakovenko
Thanks for your help.

On Wed, Dec 3, 2008 at 3:47 PM, Ryan Ingram [EMAIL PROTECTED] wrote:
 Yes; I had a similar question, and it turns out Num is special, or
 rather, pattern matching on integer literals is special.  See the
 thread

 http://www.nabble.com/Pattern-matching-on-numbers--td20571034.html

 The summary is that pattern matching on a literal integer is different
 than a regular pattern match; in particular:

 foo 1 = print one
 foo _ = print not one

 turns into

 foo x = if x == fromInteger 1 then one else not one

 whereas

 bar Test = print Test
 bar _ = print Not Test

 turns into

 bar x = case x of { Test - print Test ; _ - print Not Test }

 In the former case, the use of (y == fromInteger 1) means that foo
 works on any argument within the class Num (which requires Eq),
 whereas in the latter case, the use of the constructor Test directly
 turns into a requirement for a particular type for bar.

 There's no way to get special pattern matching behavior for other
 types; this overloading is specific to integer literals.

  -- ryan

 On Wed, Dec 3, 2008 at 3:05 PM, Anatoly Yakovenko [EMAIL PROTECTED] wrote:
 module Test where
 --why does this work:
 data Test = Test

 class Foo t where
   foo :: Num v = t - v - IO ()

 instance Foo Test where
   foo _ 1 = print $ one
   foo _ _ = print $ not one

 --but this doesn't?

 class Bar t where
   bar :: Foo v = t - v - IO ()

 instance Bar Test where
   bar _ Test = print $ test
   bar _ _ = print $ not test
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


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


Re: [Haskell-cafe] Re: ANNOUNCE: gitit 0.2 release - wiki using HAppS, git, pandoc

2008-12-03 Thread Anatoly Yakovenko
This is pretty cool.  I was wondering how much work would it be for
gitit to be able to use markdown from the comment sections in source
files?  It would be a really good way to manage documentation.

Basically I would like to be able to point gitit at an existing git
repo, and have it provide a wiki interface to all the documentation so
developers can view and modify it.

Thanks,
Anatoly

2008/12/3 Hugo Pacheco [EMAIL PROTECTED]:
 Hmm, I think I finally see the real problem.
 At some point when logged in, the session expires and the wiki prompts again
 for the login information. However, the cookies still assume we are logged
 in and do not allow me to log in again.
 The solution is to remove the cookies for the wiki server.
 I think this is some kind of bug with the session state.
 Regards,
 hugo
 On Wed, Dec 3, 2008 at 9:29 PM, Hugo Pacheco [EMAIL PROTECTED] wrote:

 Solved, just something with my Safari cookies, sorry.

 On Wed, Dec 3, 2008 at 8:40 PM, Hugo Pacheco [EMAIL PROTECTED] wrote:

 On a different level, I was trying the wiki on my laptop, but have now
 installed it in a remote server.
 However, with the same configurations, I can create users but not log in,
 it simply returns to the front page. It is hosted
 at http://haskell.di.uminho.pt:8080
 It does not seem to be a permissions problem, I gave full permissions to
 all gitit files and nothing changed.
 Any idea why?
 Also being an headache is configuring apache reverse proxy for
 it: http://haskell.di.uminho.pt/wiki/
 hugo

 On Wed, Dec 3, 2008 at 6:03 PM, Hugo Pacheco [EMAIL PROTECTED] wrote:

 yes, I am talking about inserting HTML inside the wiki.
 Thanks, I will check on that and report back,
 hugo

 On Wed, Dec 3, 2008 at 3:44 PM, John MacFarlane [EMAIL PROTECTED]
 wrote:

 +++ Hugo Pacheco [Dec 03 08 09:36 ]:
 Good morning,
 I wonder if it is possible to embed regular HTML code inside gitit
  (on
 0.3.2) pages, such as java applets like the following.
 APPLET CODE = GHood.class ARCHIVE = GHood.jar WIDTH = 1100
  HEIGHT =
 400 ALT = you should see an instance of GHood here, as an
  applet PARAM
 NAME = eventSource VALUE =factHylo.log PARAM NAME = delay
  VALUE
 =150 PARAM NAME = scale VALUE =75 /APPLET
 I am assuming that as a wiki, it is only possible to point to
  external
 pages.
 Thanks,
 hugo

 Of course you can put any HTML you like in the page template
 (template.html).  But I assume you are asking about HTML inside the
 wiki
 pages themselves. Although markdown allows embedded HTML, gitit uses
 pandoc's
 HTML sanitization feature, so things that might be dangerous (like
 applets) will be filtered out and replaced by comments.

 You could easily modify the code to remove the santitization feature.
 Just change the textToPandoc function so that stateSanitizeHtml is set
 to
 False.

 John




 --
 www.di.uminho.pt/~hpacheco



 --
 www.di.uminho.pt/~hpacheco



 --
 www.di.uminho.pt/~hpacheco



 --
 www.di.uminho.pt/~hpacheco

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


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


[Haskell-cafe] Re: ANNOUNCE: gitit 0.2 release - wiki using HAppS, git, pandoc

2008-12-03 Thread Anatoly Yakovenko
On Wed, Dec 3, 2008 at 5:54 PM, John MacFarlane [EMAIL PROTECTED] wrote:
 +++ Anatoly Yakovenko [Dec 03 08 17:03 ]:
 This is pretty cool.  I was wondering how much work would it be for
 gitit to be able to use markdown from the comment sections in source
 files?  It would be a really good way to manage documentation.

 Basically I would like to be able to point gitit at an existing git
 repo, and have it provide a wiki interface to all the documentation so
 developers can view and modify it.

 You can do something like that now. You can specify the repository
 directory in a configuration file. Anything in the repository (even
 in subdirectories) with a .page extension will be served up as a
 wiki page. So you'd have to use a .page extension for your markdown
 documentation. Everything else in the repository will appear in the
 index. Source code files will be automatically syntax-highlighted, and
 you can even view history and diffs through the wiki interface.

cool.  Does it add any other files to the reposoitory?  Could you use
it over a read only one?

 But I guess what you want is for the documentation to be in comments
 in the source files themselves, not in separate files.  I'm not sure
 how to do that -- would the idea be to show just the documentation,
 perhaps marked off with some special notation, and not the source?
 But then we lose a nice feature, the ability to view source files.
 I'm open to ideas.

I was thinking it would show both the documentation and the source,
but have the documentation as the editable part of the page.  Do you
think that's possible?

Or it could parse out the documentation and show 2 dynamically
generated pages, one for just the docs and one for the source.  But i
think it would be useful to be able to see the documentation in the
context of the source that its referring to.

Unfortunately I am not a web guy, so i have no idea how hard any of
this would be :).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ANNOUNCE: gitit 0.2 release - wiki using HAppS, git, pandoc

2008-12-03 Thread Anatoly Yakovenko
 Being practical, this is very close to the markdownish literate haskell you
 are suggesting.
 hugo

yea, i agree.  But is there any way to generalize this to non haskell projects?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What *not* to use Haskell for

2008-11-11 Thread Anatoly Yakovenko
Has there been any progress in getting ghc set up for porting to non
x86/unix/windows platforms?  Can it generate ropi code?  It would also
be nice to be able to compile to C that rvct/arm tools can compile in
thumb mode.  Its whats stopping me from trying to use it for mobile
development.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] is there a way to pretty print a module?

2008-10-30 Thread Anatoly Yakovenko
is there a way to pretty print a module?
like:

module Main where
import Language.Haskell.TH
main = do
 print $ pprint Main
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: is there a way to pretty print a module?

2008-10-30 Thread Anatoly Yakovenko
 is there a way to pretty print a module?
 like:

 module Main where
 import Language.Haskell.TH
 main = do
  print $ pprint Main

 haskell-src should be able to do that.

I think haskell-src requires you to read the module at run time.  I
want to embed the contents of the module in my program.  Basically a
program that can print itself.

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


Re: [Haskell-cafe] Re: is there a way to pretty print a module?

2008-10-30 Thread Anatoly Yakovenko
i guess am missing something:

$ cat ./test.hs
 {-# LANGUAGE TemplateHaskell#-}
module Main where

import Language.Haskell.TH
import qualified Data.ByteString as BS

embedFile :: FilePath - Q BS.ByteString
embedFile ff = runIO $ BS.readFile ff


main = do
   me - runQ $ embedFile ./test.hs
   print me

$ ghc --make test.hs
[1 of 1] Compiling Main ( test.hs, test.o )
Linking test ...

 $ ./test
 {-# LANGUAGE TemplateHaskell#-}\nmodule Main where\n\nimport
Language.Haskell.TH\nimport qualified Data.ByteString as
BS\n\nembedFile :: FilePath - Q BS.ByteString\nembedFile ff = runIO $
BS.readFile ff\n\n\nmain = do\n   me - runQ $ embedFile
\./test.hs\\n   print me\n\n

$ mv test.hs test.hs.old

$ ./test
test: ./test.hs: openBinaryFile: does not exist (No such file or directory)

i was hoping test.hs would become part of the executable.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: is there a way to pretty print a module?

2008-10-30 Thread Anatoly Yakovenko
cool, i found this:

http://www.nabble.com/template-haskellinclude-a-file--td19462913.html

$ cat test.hs
{-# LANGUAGE TemplateHaskell#-}
module Main where

import Language.Haskell.TH
import EmbedStr

me = $(embedStr $ readFile ./test.hs)

main = do
   print $ me

$ cat EmbedStr.hs
{-# LANGUAGE TemplateHaskell#-}
module EmbedStr where

import Language.Haskell.TH
import Language.Haskell.TH.Syntax (lift)

embedStr:: IO String - ExpQ
embedStr str =  lift = runIO str
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] using ghc as a library

2008-10-28 Thread Anatoly Yakovenko
On Mon, Oct 27, 2008 at 3:23 PM, Thomas Schilling
[EMAIL PROTECTED] wrote:
 Not at the moment.  I was thinking about abstracting out the finder,
 which might be useful for other things, too.  Can you maybe describe
 your actual goal?  Adding an import foo/bar would not parse, so you
 must have some kind of preprocessing going on, so you might be able to
 insert some dummy imports there which you then have to provide.  E.g.:
 import foo/bar.hs ~~ import CafeF00d.Foo.Bar, and you then copy (or
 symlink) foo/bar.hs to CafeF00d/Foo/Bar.hs.  You can put those into a
 special directory which you prepend to the list of searched
 directories.

Well my immediate goal was to see if i can make a generic build system
ala ruby's rake or rant in haskell.  But the overall goal was to
understand how the compiler works and what i can do with it.  I hate
gui's so i prefer having a interface to my programs that's as
expressive as the language that they are written in, and being
typesafe is always nice :).

I think you suggestion on using the preprocessor is an excellent idea,
and should at least get me there.  Can you point me to some
documentation on what gcc expects from the preprocessor?  Does it
basically expect something that has the same interface as cpp?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] using ghc as a library

2008-10-28 Thread Anatoly Yakovenko
On Tue, Oct 28, 2008 at 2:34 AM, Thomas Schilling
[EMAIL PROTECTED] wrote:
 GHC contains its own preprocessor, it just needs to be activated using
 -cpp on the command line or {-# LANGUAGE CPP #-} inside the file.
 However, I wasn't suggesting that.  I was suggesting that before you
 hand the input to the ghc api, you substitute all occurences of import
 foo by something that the haskell parser understands.

Thanks a lot for your help.  I am trying your suggestion at the moment.

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


Re: [Haskell-cafe] using ghc as a library

2008-10-27 Thread Anatoly Yakovenko
On Mon, Oct 27, 2008 at 3:27 AM, Thomas Schilling
[EMAIL PROTECTED] wrote:
 I'm not quite sure what you are trying to do.  But for what it's
 worth, you can load a specific file via

  setTarget [Target (TargetFile foo/blah.hs) True Nothing]

right, but I cant do that from inside a module in place of an import.
Is there any way to for me to somehow tell ghc, or my wrapper, that I
want to load a module from a specific directory, regardless of what
the current include flags are?

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


Re: [Haskell-cafe] using ghc as a library

2008-10-26 Thread Anatoly Yakovenko
 Hi, Anatoly

 Sorry for don't answering your question in the first place, but for this
 kind of tasks I believe you might be better off using some lightweight
 wrapper of the GHC Api.

thanks, that's really cool, but I am trying to figure out a way to
embed haskell into another program so i can control and configure it
using haskell.  I managed to get farther by using the GHC api's that
manipulate the ModuleInfo structure, but I am kind of stuck right now
trying to figure out how to allow different scripts import each other.

The problem is that i dont wan't to have to structure the input
scripts as I would a regular haskell project.  I basically want to be
able to do

import foo/blah.hs

and read the blah.hs file directly.  Any ideas?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] any idea why cabal install cabal-install cant update itself in windows?

2008-10-23 Thread Anatoly Yakovenko
On Wed, Oct 22, 2008 at 8:48 PM, Austin Seipp [EMAIL PROTECTED] wrote:
 Windows will not let you modify/delete binaries if they're running as a
 process, and it won't let you delete .DLL files that're in use by
 applications either (mapped to shared memory, that is.) So cabal
 install cannot overwrite the cabal.exe binary after it builds it,
 because it's already running.

looks like i just needed to fix my paths.  I had the default ghc bin
directory before the directory where cabal installs its binaries.  But
after i fixed that, i ran into the windows problem, which i fixed by
just copying the binary to a temporary location.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] any idea why cabal install cabal-install cant update itself in windows?

2008-10-22 Thread Anatoly Yakovenko
C:\Documents and Settings\anatolyycabal install cabal-install
Resolving dependencies...
'cabal-install-0.6.0' is cached.
Configuring cabal-install-0.6.0...
Preprocessing executables for cabal-install-0.6.0...
Building cabal-install-0.6.0...
...
Linking dist\build\cabal\cabal.exe ...
Installing: C:\Documents and Settings\anatolyy\Application Data\cabal\bin

C:\Documents and Settings\anatolyycabal --version
cabal-install version 0.5.2
using version 1.4.0.2 of the Cabal library
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] code generation

2008-10-21 Thread Anatoly Yakovenko
you can also write an interpreter in haskell that will typecheck using GADT's

http://www.informatik.uni-bonn.de/~ralf/publications/With.pdf

http://www.haskell.org/pipermail/haskell/2005-May/015815.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] is the a way to reinstall a package with cabal install?

2008-10-09 Thread Anatoly Yakovenko
is the a way to reinstall a package with cabal install?  I want to add
profiling support to a libarary.

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


Re: [Haskell-cafe] Re: having fun with GADT's

2008-09-30 Thread Anatoly Yakovenko
has the with syntax described in

 http://www.haskell.org/pipermail/haskell/2005-May/015815.html

been replaced with the where syntax?

so

data Foo a where
  FooInt :: FooInt

the same thing as

data Foo A = FooInt with a = Int
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: haskell blas bindings: does iomatrix gemv transposing of matrix a?

2008-09-26 Thread Anatoly Yakovenko
 e = exp 1.0
 sigmoid xx = 1.0 / (1 + (e ** (1.0 * xx)))

 That 1.0 * xx caught my eye.

 In case this was an oversight on your part: if you mean the usual sigmoid
 function, that should be 1.0 / (1 + (e ** (0.0 - x))).

i had a different constant there before.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Injecting Haskell into C

2008-09-25 Thread Anatoly Yakovenko
 I have not been following the details, but would you consider writing up your 
 example on the GHC user guide Wiki?
http://haskell.org/haskellwiki/GHC/Using_the_FFI

 It's a very good way to share your experience with others.

I got that example from Claude Heiland-Allen.  Unless he has any
objections, or would like to do it himself, I can put it on the wiki.

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


Re: [Haskell-cafe] Injecting Haskell into C

2008-09-25 Thread Anatoly Yakovenko
 I have not been following the details, but would you consider writing up 
 your example on the GHC user guide Wiki?
http://haskell.org/haskellwiki/GHC/Using_the_FFI

 It's a very good way to share your experience with others.

 I got that example from Claude Heiland-Allen.  Unless he has any
 objections, or would like to do it himself, I can put it on the wiki.

actually, its already on there,
http://haskell.org/haskellwiki/GHC/Using_the_FFI#Callbacks_into_Haskell_from_foreign_code

 Anatoly

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


[Haskell-cafe] Re: haskell blas bindings: does iomatrix gemv transposing of matrix a?

2008-09-24 Thread Anatoly Yakovenko
is there anyway the modifyWith functions could work on uboxed types?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: haskell blas bindings: does iomatrix gemv transposing of matrix a?

2008-09-24 Thread Anatoly Yakovenko
 is there anyway the modifyWith functions could work on uboxed types?

 If they're inlined, the modify functions on boxed types may well end up
 unboxed.

 What's the particular problem you're having?

well, after inspecting a little further its not so bad actually.  i
was comparing

module Main where

import qualified Data.Vector.Dense.IO as Vector
import Control.Monad

e = exp 1.0
sigmoid xx = 1.0 / (1 + (e ** (1.0 * xx)))

type Vec = Vector.IOVector Int Double
main = do
   let size = 10
   ff::Vec - Vector.newListVector size $ repeat 0.5
   replicateM_ 1000 $ Vector.modifyWith (sigmoid) ff
   putStrLn $ done

to this:

#include math.h
#include stdlib.h
#include stdio.h

double sigmoid(double xx) {
   return 1.0 / (1.0 + (pow(M_E, (1.0 * xx;
}

int main() {
   int size = 10;
   int times = 1000;
   int ii,jj;
   double* array = malloc(sizeof(double)*size);
   for(jj = 0; jj  size; ++jj) {
  array[jj] = 0.5;
   }
   for(ii = 0; ii  times; ++ii) {
  for(jj = 0; jj  size; ++jj) {
 array[jj] = sigmoid(array[jj]);
  }
   }
   printf(done\n);
}

the haskell version does ok, or 0m37.937s vs 0m23.492s in C.  I am
compiling with these options: -O2 -fexcess-precision
-funbox-strict-fields -fglasgow-exts -fbang-patterns -prof -auto-all,
and O2 for gcc.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Injecting Haskell into C

2008-09-24 Thread Anatoly Yakovenko
you'll find this example really helpfull


-- Forwarded message --
From: Claude Heiland-Allen [EMAIL PROTECTED]
Date: 2008/6/5
Subject: Re: [Haskell-cafe] example of FFI FunPtr
To: Galchin, Vasili [EMAIL PROTECTED]
Cc: haskell haskell-cafe@haskell.org


Galchin, Vasili wrote:

 Hello,

   I want to model a Haskell function that is a callback from C. I have
 only found one example in the unix package's Semaphore.hsc, which apparently
 is not used. I want to be able to marshall a Haskell function that is a
 first class citizen residing in a Haskell data type and pass to a C function
 via FFI. Are there examples of this?

Attached is a simple example.

The main thing to note is 'foreign import ccall wrapper' which gives
you a factory for turning Haskell functions into foreign function
pointers.

More information:

http://www.cse.unsw.edu.au/~chak/haskell/ffi/


Claude
--
http://claudiusmaximus.goto10.org


CallBacker: CallBacker.hs callerback.c callerback.h
   ghc -O2 -Wall -fffi -o CallBacker CallBacker.hs callerback.c

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
module Main(main) where

import Foreign.C.Types(CDouble)
import Foreign.Ptr(FunPtr, freeHaskellFunPtr)

foreign import ccall wrapper
  wrap :: (CDouble - CDouble) - IO (FunPtr (CDouble - CDouble))

foreign import ccall callerback.h twice
  twice :: FunPtr (CDouble - CDouble) - CDouble - IO CDouble

square :: CDouble - CDouble
square x = x * x

main :: IO ()
main = do
  squareW - wrap square
  let x = 4
  y - twice squareW x
  z - twice squareW y
  print y
  print z
  freeHaskellFunPtr squareW
#include callerback.h

double twice(d2d f, double x) {
  return f(f(x));
}

#ifndef CALLERBACK_H
#define CALLERBACK_H
typedef double (d2d)(double);
double twice(d2d f, double x);
#endif
CallBacker: CallBacker.hs callerback.c callerback.h
ghc -O2 -Wall -fffi -o CallBacker CallBacker.hs callerback.c
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] how do i use quickcheck in the IO monad?

2008-09-22 Thread Anatoly Yakovenko
If i have functions in the IO monad, is there a way to use quickcheck
to test them?  I have a bunch of C bindings that unfortunately are not
safe.  But i would like to be able to use QuickCheck to test them.

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


Re: [Haskell-cafe] Re: having fun with GADT's

2008-09-22 Thread Anatoly Yakovenko
 data Nat a where
Z :: Nat a
S :: Nat a - Nat (S a)

 data Z
 data S a

I thought I was getting this, but this part is confusing.  What
exactly does declaring data Z do?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: having fun with GADT's

2008-09-22 Thread Anatoly Yakovenko
 data Nat a where
Z :: Nat a
S :: Nat a - Nat (S a)

 data Z
 data S a

 n00 = Z
 n01 = S n00
 n02 = S n01
 n03 = S n02
 n04 = S n03

 data MaxList t where
   Nil :: MaxList a
   Cons :: Nat a - MaxList a - MaxList a

 a = Cons n02 $ Cons n02 $ Cons n01 $ Nil
 --- :t a gives forall a. MaxList (S (S a)) which tells you exactly
 --- what you want: elements are at least 2.

 mlTail :: forall t. MaxList t - MaxList t
 mlTail (Cons h t) = t

Is there a way to define a function that only takes a list with a max
of 1?  Because

only1 :: MaxList (S a) - String
only1 _ = only1

will work over
 a = Cons n02 $ Cons n02 $ Cons n01 $ Nil
without any problems
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: having fun with GADT's

2008-09-22 Thread Anatoly Yakovenko
 type One = S Z
 type Two = S One
 etc.

why does:

data Nat a where
   Z :: Nat a
   S :: Nat a - Nat (S a)

data Z
data S a

type One = S Z
n00 = Z
n01::One = S n00

give me:

test.hs:10:11:
Couldn't match expected type `One'
   against inferred type `Nat (S a)'
In the expression: S n00
In a pattern binding: n01 :: One = S n00
Failed, modules loaded: none.


or better yet, how is type S Z different from, n01 :: forall a. Nat (S a)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] having fun with GADT's

2008-09-20 Thread Anatoly Yakovenko
I dont remember where i saw it, but i think someone had an example of
a list whose type is the maximum element in the list.  I've been
trying to reproduce that with GADT's.

data One = One
data Two = Two
data Three = Three

data MaxList t where
   Elem1 :: MaxList One
   Elem2 :: MaxList Two
   ML1Cons1 :: MaxList One - MaxList One - MaxList One
   ML1Cons2 :: MaxList One - MaxList Two - MaxList Two
   ML2Cons1 :: MaxList Two - MaxList One - MaxList Two
   ML2Cons2 :: MaxList Two - MaxList Two - MaxList Two

a = ML2Cons2 Elem2 $ ML2Cons1 Elem2 $ ML1Cons1 Elem1 $ Elem1

so one problem is the tedium of defining a cons for each possible
combination.  The other problem is that i cant define a usefull tail
that makes any sense.

mlTail :: MaxList Two - MaxList t
mlTail (ML2Cons2 a b) = b
mlTail (ML2Cons1 a b) = b

this one doesn't work, and probably because there is nothing that i
could do with the return value.

mlTail :: MaxList Two - MaxList Two
mlTail (ML2Cons2 a b) = b
mlTail (ML2Cons1 a b) = b  --wont compile because b is a MaxList One

will only work for lists that only contain Two's, which is not what i
want either.  So is this somehow possible?

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


Re: [Haskell-cafe] Re: having fun with GADT's

2008-09-20 Thread Anatoly Yakovenko
 data One = One
 data Two = Two
 data Three = Three

 data MaxList t where
Elem1 :: MaxList One
Elem2 :: MaxList Two
ML1Cons1 :: MaxList One - MaxList One - MaxList One
ML1Cons2 :: MaxList One - MaxList Two - MaxList Two
ML2Cons1 :: MaxList Two - MaxList One - MaxList Two
ML2Cons2 :: MaxList Two - MaxList Two - MaxList Two

 a = ML2Cons2 Elem2 $ ML2Cons1 Elem2 $ ML1Cons1 Elem1 $ Elem1

 so one problem is the tedium of defining a cons for each possible
 combination.  The other problem is that i cant define a usefull tail
 that makes any sense.

 mlTail :: MaxList Two - MaxList t
 mlTail (ML2Cons2 a b) = b
 mlTail (ML2Cons1 a b) = b

 this one doesn't work, and probably because there is nothing that i
 could do with the return value.

 Your problem in this example is that the t in MaxList t is universally
 quantified when it needs to be existentially quantified. The following
 definition encodes the existential quantification as a rank-2 type:

 mlTail :: MaxList n - (forall t. MaxList t - a) - a
 mlTail (ML1Cons1 h t) f = f t
 mlTail (ML1Cons2 h t) f = f t
 mlTail (ML2Cons1 h t) f = f t
 mlTail (ML2Cons2 h t) f = f t

 It works with the rest of your code unmodified.

how do i define (forall t. MaxList t - a)?  It seems like i just
pushed the problem somewhere else.

 mlTail :: MaxList Two - MaxList Two
 mlTail (ML2Cons2 a b) = b
 mlTail (ML2Cons1 a b) = b  --wont compile because b is a MaxList One

 will only work for lists that only contain Two's, which is not what i
 want either.  So is this somehow possible?

 This example here suggests that you are happy merely with a (not necessarily
 tight) upper bound on the list elements. The following code solves your 
 problem
 in this case, using only type unification and not fundeps or TFs:

 data Nat a where
Z :: Nat a
S :: Nat a - Nat (S a)

 data Z
 data S a

 n00 = Z
 n01 = S n00
 n02 = S n01
 n03 = S n02
 n04 = S n03

 data MaxList t where
   Nil :: MaxList a
   Cons :: Nat a - MaxList a - MaxList a

 a = Cons n02 $ Cons n02 $ Cons n01 $ Nil
 --- :t a gives forall a. MaxList (S (S a)) which tells you exactly
 --- what you want: elements are at least 2.

 mlTail :: forall t. MaxList t - MaxList t
 mlTail (Cons h t) = t
 --- unfortunately, you lose information here if the first
 --- element is larger than the rest.

Thanks, that's really cool.  Is there a way to keep  a tight upper
bound on the list using this method?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: haskell blas bindings: does iomatrix gemv transposing of matrix a?

2008-09-17 Thread Anatoly Yakovenko
 I made the decision to make herm an O(1) operation.  This means you don't 
 have to pass transpose arguments to the multiplication routines.  When you 
 do, for example:

 let a = listMatrix (2,3) [1..6]
 x = listVector 2 [1, -1]
 in herm a * x

 this gets implemented as a call to gemv with transa set to ConjTrans.

Ah, i see, i didn't see that function.  That's pretty slick actually.


 The new version is pretty typeclass-heavy, since that's the only way I know 
 how to support both ST and IO.  Consequently, there have been some 
 performance regressions.  I have some optimization ideas (in the TODO) 
 file, but I do not have time to implement them right now.  If you or anyone 
 else would like to help with this or anything else, I would be glad to have 
 you aboard the development team.

I would be glad to help.  Its probably about time i learned the type
system anyways.

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


[Haskell-cafe] haskell blas bindings: does iomatrix gemv transposing of matrix a?

2008-09-16 Thread Anatoly Yakovenko
Hey Patric,

Thanks for your great work on the blas bidnings.  I have a question on
gemv.  I thought its possible for blas to transpose the input matrix
before doing the multiplication.  Is it possible to do that with the
haskell bindings?  Or am I mistaken in how gemv is used

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


Re: [Haskell-cafe] blas bindings, why are they so much slower the C?

2008-06-27 Thread Anatoly Yakovenko
 I suspect that it is your initialization that is the difference.  For
 one thing, you've initialized the arrays to different values, and in
 your C code you've fused what are two separate loops in your Haskell
 code.  So you've not only given the C compiler an easier loop to run
 (since you're initializing the array to a constant rather than to a
 sequence of numbers), but you've also manually optimized that
 initialization.  In fact, this fusion could be precisely the factor of
 two.  Why not see what happens in Haskell if you create just one
 vector and dot it with itself? (of course, that'll also make the blas
 call faster, so you'll need to be careful in your interpretation of
 your results.)

The difference cant be in the initialization.   I am calling the dot
product a million times, the malloc and init in both cases are
insignificant.  Also, fusing the two loops in C probably wont help,
if anything having each loop run separate is likely to be faster and
result in less cache misses.

In this case, i am using vectors of size 10 only, and calling the loop
10 million times, haskell is far far slower, or 35 times.  That's
pretty crappy.


$ cat htestdot.hs
{-# OPTIONS_GHC -O2 -fexcess-precision -funbox-strict-fields
-fglasgow-exts -fbang-patterns -lcblas#-}
module Main where

import Data.Vector.Dense.IO
import Control.Monad

main = do
   let size = 10
   let times = 10*1000*1000
   v1::IOVector Int Double - newListVector size $ replicate size 0.1
   v2::IOVector Int Double - newListVector size $ replicate size 0.1
   sum - foldM (\ ii zz - do
  rv - v1 `getDot` v2
  return $ zz + rv
  ) 0.0 [0..times]
   print $ sum


$ ghc --make htestdot.hs
$ time ./htestdot
1.0001e7

real0m17.328s
user0m17.320s
sys 0m0.010

$ cat testdot.c
#include cblas.h
#include stdlib.h
#include stdio.h
#include string.h

int main() {
   int size = 10;
   int times = 10*1000*1000;
   int ii = 0;
   double dd = 0.0;
   double* v1 = malloc(sizeof(double) * (size));
   double* v2 = malloc(sizeof(double) * (size));
   for(ii = 0; ii  size; ++ii) {
  v1[ii] = 0.1;
   }
   for(ii = 0; ii  size; ++ii) {
  v2[ii] = 0.1;
   }
   for(ii = 0; ii  times; ++ii) {
  dd += cblas_ddot(size, v1, 1, v2, 1);
   }
   free(v1);
   free(v2);
   printf(%f\n, dd);
   return 0;
}

$ gcc -O2 testdot.c -lcblas -o testdot
$ time ./testdot
99.999839

real0m0.491s
user0m0.480s
sys 0m0.020s


Just to make sure that fold isnt causing the slowdown, i reverted the
haskell program to use the mapM_, i still got almost the same
performance:

$ cat htestdot.hs
{-# OPTIONS_GHC -O2 -fexcess-precision -funbox-strict-fields
-fglasgow-exts -fbang-patterns -lcblas#-}
module Main where

import Data.Vector.Dense.IO
import Control.Monad

main = do
   let size = 10
   let times = 10*1000*1000
   v1::IOVector Int Double - newListVector size $ replicate size 0.1
   v2::IOVector Int Double - newListVector size $ replicate size 0.1
   mapM_ (\ ii - do v1 `getDot` v2) [0..times]
$ ghc --make htestdot

$ time ./htestdot

real0m15.660s
user0m15.630s
sys 0m0.030s

This is what the profiler has to say:

 $ cat htestdot.prof
Fri Jun 27 18:06 2008 Time and Allocation Profiling Report  (Final)

   htestdot +RTS -p -RTS

total time  =   22.00 secs   (1100 ticks @ 20 ms)
total alloc = 3,320,010,716 bytes  (excludes profiling overheads)

COST CENTREMODULE   %time %alloc

main   Main 100.0  100.0



individualinherited
COST CENTRE  MODULE
   no.entries  %time %alloc   %time %alloc

MAIN MAIN
 1   0   0.00.0   100.0  100.0
 mainMain
   222   1  93.6   88.093.6   88.0
 CAF Main
   216   5   0.00.0 6.4   12.0
  main   Main
   223   0   6.4   12.0 6.4   12.0
 CAF GHC.Handle
   168   3   0.00.0 0.00.0
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] blas bindings, why are they so much slower the C?

2008-06-27 Thread Anatoly Yakovenko
i get the same crappy performance with:

$ cat htestdot.hs
{-# OPTIONS_GHC -O2 -fexcess-precision -funbox-strict-fields
-fglasgow-exts -fbang-patterns -lcblas#-}
module Main where

import Data.Vector.Dense.IO
import Control.Monad

main = do
   let size = 10
   let times = 10*1000*1000
   v1::IOVector Int Double - newListVector size $ replicate size 0.1
   v2::IOVector Int Double - newListVector size $ replicate size 0.1
   replicateM_ times $ v1 `getDot` v2



On Fri, Jun 27, 2008 at 7:41 PM, Dan Doel [EMAIL PROTECTED] wrote:
 On Friday 27 June 2008, Anatoly Yakovenko wrote:
 $ cat htestdot.hs
 {-# OPTIONS_GHC -O2 -fexcess-precision -funbox-strict-fields
 -fglasgow-exts -fbang-patterns -lcblas#-}
 module Main where

 import Data.Vector.Dense.IO
 import Control.Monad

 main = do
let size = 10
let times = 10*1000*1000
v1::IOVector Int Double - newListVector size $ replicate size 0.1
v2::IOVector Int Double - newListVector size $ replicate size 0.1
sum - foldM (\ ii zz - do
   rv - v1 `getDot` v2
   return $ zz + rv
   ) 0.0 [0..times]
print $ sum

 Hackage is down for the time being, so I can't install blas and look at the
 core for your program. However, there are still some reasons why this code
 would be slow.

 For instance, a brief experiment seems to indicate that foldM is not a good
 consumer in the foldr/build sense, so no deforestation occurs. Your program
 is iterating over a 10-million element lazy list. That's going to add
 overhead. I wrote a simple test program which just adds 0.1 in each
 iteration:

  snip 

 {-# LANGUAGE BangPatterns #-}

 module Main (main) where

 import Control.Monad

 main = do
  let times = 10*1000*1000
  sum - foldM (\_ zz - return $ zz + 0.1) 0.0 [0..times]
 --  sum - foo 0 times 0.0
  print $ sum

 foo :: Int - Int - Double - IO Double
 foo k m !zz
  | k = m = foo (k+1) m (zz + 0.1)
  | otherwise = return zz

  snip 

 With foldM, it takes 2.5 seconds on my machine. If you comment that line, and
 use foo instead, it takes around .1 seconds. So that's a factor of what, 250?
 That loop allows for a lot more unboxing, which allows much better code to be
 generated.

 When Hackage comes back online, I'll take a look at your code, and see if I
 can make it run faster, but you might want to try it yourself in the time
 being. Strictifying the addition of the accumulator is probably a good idea,
 for instance.

 Cheers,
 -- Dan

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


[Haskell-cafe] blas bindings, why are they so much slower the C?

2008-06-18 Thread Anatoly Yakovenko
here is the C:

#include cblas.h
#include stdlib.h

int main() {
   int size = 1024;
   int ii = 0;
   double* v1 = malloc(sizeof(double) * (size));
   double* v2 = malloc(sizeof(double) * (size));
   for(ii = 0; ii  size*size; ++ii) {
  double _dd = cblas_ddot(0, v1, size, v2, size);
   }
   free(v1);
   free(v2);
}

this is the haskell:

module Main where

import Data.Vector.Dense.IO

main = do
   let size = 1024
   v1::IOVector Int Double - newListVector size [0..]
   v2::IOVector Int Double - newListVector size [0..]
   mapM_ (\ ii - do v1 `getDot` v2) [0..size*size]

time ./testdot

real0m0.017s
user0m0.010s
sys 0m0.010s

time ./htestdot

real0m4.692s
user0m4.670s
sys 0m0.030s

so like 250x difference

htestdot.prof is no help

   Tue Jun 17 20:46 2008 Time and Allocation Profiling Report  (Final)

  htestdot +RTS -p -RTS

   total time  =3.92 secs   (196 ticks @ 20 ms)
   total alloc = 419,653,032 bytes  (excludes profiling overheads)

COST CENTREMODULE   %time %alloc

main   Main  88.3   83.0
CAFMain  11.7   17.0



individualinherited
COST CENTRE  MODULE
   no.entries  %time %alloc   %time %alloc

MAIN MAIN
 1   0   0.00.0   100.0  100.0
 CAF Main
   216   7  11.7   17.0   100.0  100.0
  main   Main
   222   1  88.3   83.088.3   83.0
 CAF GHC.Float
   187   1   0.00.0 0.00.0
 CAF GHC.Handle
   168   3   0.00.0 0.00.0
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] blas bindings, why are they so much slower the C?

2008-06-18 Thread Anatoly Yakovenko
 #include cblas.h
 #include stdlib.h

 int main() {
   int size = 1024;
   int ii = 0;
   double* v1 = malloc(sizeof(double) * (size));
   double* v2 = malloc(sizeof(double) * (size));
   for(ii = 0; ii  size*size; ++ii) {
  double _dd = cblas_ddot(0, v1, size, v2, size);
   }
   free(v1);
   free(v2);
 }

 Your C compiler sees that you're not using the result of cblas_ddot,
 so it doesn't even bother to call it. That loop never gets run. All
 your program does at runtime is call malloc and free twice, which is
 very fast :-)

C doesn't work like that :).  functions always get called.  but i did
find a problem with my C code, i am incorrectly calling the dot
production function:

#include cblas.h
#include stdlib.h
#include stdio.h
#include string.h

int main() {
   int size = 1024;
   int ii = 0;
   double dd = 0.0;
   double* v1 = malloc(sizeof(double) * (size));
   double* v2 = malloc(sizeof(double) * (size));
   for(ii = 0; ii  size; ++ii) {
  v1[ii] = 0.1;
  v2[ii] = 0.1;
   }
   for(ii = 0; ii  size*size; ++ii) {
  dd += cblas_ddot(size, v1, 0, v2, 0);
   }
   free(v1);
   free(v2);
   printf(%f\n, dd);
   return 0;
}

time ./testdot
10737418.240187

real0m2.200s
user0m2.190s
sys 0m0.010s

So C is about twice as fast.  I can live with that.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] -fvia-C error

2008-06-12 Thread Anatoly Yakovenko
any idea what could be causing this error when i add the -fvia-C option

/tmp/ghc32300_0/ghc32300_0.hc:6:23:
 error: SFMT_wrap.h: No such file or directory
make: *** [release] Error 1

I am also passing these options:

-O2 -fexcess-precision -funbox-strict-fields -fglasgow-exts
-fbang-patterns -lcblas

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


Re: [Haskell-cafe] -fvia-C error

2008-06-12 Thread Anatoly Yakovenko
 When compiling something linked against the mersenne random package?

yes, does it not work with fvia-C?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] blas: ghc-6.8.2: unable to load package `blas-0.4'

2008-06-10 Thread Anatoly Yakovenko
Patric,

I am trying to use your blas package, but I am getting a missing symbol error.

 import Data.Matrix.Dense.IO
 mm::(IOMatrix (Int,Int) Double) - newListMatrix (1,1) [1.0]
Loading package storable-complex-0.1 ... linking ... done.
Loading package ieee-0.1 ... linking ... done.
Loading package old-locale-1.0.0.0 ... linking ... done.
Loading package old-time-1.0.0.0 ... linking ... done.
Loading package random-1.0.0.0 ... linking ... done.
Loading package QuickCheck-1.1.0.0 ... linking ... done.
Loading package blas-0.4 ... linking ... interactive:
/usr/lib/blas-0.4/ghc-6.8.2/HSblas-0.4.o: unknown symbol `cblas_ddot'
ghc-6.8.2: unable to load package `blas-0.4'

any ideas what i am missing?

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


Re: [Haskell-cafe] blas: ghc-6.8.2: unable to load package `blas-0.4'

2008-06-10 Thread Anatoly Yakovenko
 /usr/lib/blas-0.4/ghc-6.8.2/HSblas-0.4.o: unknown symbol `cblas_ddot'
 ghc-6.8.2: unable to load package `blas-0.4'

 any ideas what i am missing?

 Missing -lcblas perhaps? The C library isn't being found.

$ ll /usr/lib/libcblas.*
lrwxrwxrwx 1 root root 25 Jun 10 20:57 /usr/lib/libcblas.a -
blas/reference/libcblas.a
lrwxrwxrwx 1 root root 26 Jun 10 20:57 /usr/lib/libcblas.so -
blas/reference/libcblas.so
lrwxrwxrwx 1 root root 28 Jun 10 20:57 /usr/lib/libcblas.so.0 -
blas/reference/libcblas.so.0

I think its installed correctly,

$ nm /usr/lib/libcblas.*  | grep cblas_ddot
cblas_ddot.o:
 T cblas_ddot
nm: /usr/lib/libcblas.so: no symbols
nm: /usr/lib/libcblas.so.0: no symbols
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] blas: ghc-6.8.2: unable to load package `blas-0.4'

2008-06-10 Thread Anatoly Yakovenko
nevermind, i am a little slow today.  ghci -lcblas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: hmatrix

2008-06-05 Thread Anatoly Yakovenko
Thanks, that's exactly what i was looking for.

On Thu, Jun 5, 2008 at 8:16 AM, Alberto Ruiz [EMAIL PROTECTED] wrote:
 Hello Bulat and Anatoly,

 I have written a first version of an interface to inplace updates in the ST
 monad for the hmatrix vectors and matrices. Many things must be
 improved (range checking, documentation, etc.) but I hope that the general
 idea makes sense.

 A few usage examples:

 http://perception.inf.um.es/~aruiz/darcs/hmatrix/examples/inplace.hs

 Code:

 http://perception.inf.um.es/~aruiz/darcs/hmatrix/lib/Data/Packed/ST.hs

 http://perception.inf.um.es/~aruiz/darcs/hmatrix/doc/html/Data-Packed-ST.html

 Any suggestion will be welcome. I'm impressed by the power of the ST monad,
 it is extremely useful and elegant. Thank you again for your help!

 In the future I will also try to include efficient conversions to/from
 standard Haskell arrays and those of other related libraries like Jed
 Brown's CArray.

 Thanks,

 Alberto


 Bulat Ziganshin wrote:

 Hello Alberto,

 Tuesday, June 3, 2008, 12:56:50 PM, you wrote:

 Good! So you can easily hide the IO operations in the ST monad. I will
 definitely look into it.

 from implementation POV ST monad is nothing but renamed IO monad which
 exports only subset of its operations which are guaranteed to safe.
 or, saying in other words, it's just type hackery around IO monad that
 provides safe operations

 it's possible to define ST monad and its operations as following:

 newtype ST s a = forall s. ST_Constructor (IO a)

 unsafeIOtoSt action = ST_Constructor action

 runST (ST_Constructor action) = unsafePerformIO action

 newtype STRef s a = forall s. STRef (IORef a)

 readSTRef (STRef ref)  =  unsafeIOtoSt (readIORef ref)

 and so on. GHC uses technically (but not ideologically!) different
 implementation where both monads are specializations of one generic
 type. while Hugs afair uses exactly this approach. you may also look
 at ArrayRef lib which reimplements arrays/refs for both compilers in
 more unified way

 anyway, because ST is just IO monad modulo type tricks, you can
 execute any IO action inside ST by lifting it with unsafeIOtoSt


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


[Haskell-cafe] Re: hmatrix

2008-06-02 Thread Anatoly Yakovenko
 do you have any plans to provide an interface for inplace updates?

 Yes, I will try to write a simple version of Data.Array.ST...


I can try to help you, although I still dont quite grok monads.
Wouldn't it be more efficient to use StorableArray, so you can cast
from and to C?  I am not sure how vectors and matrixes are represented
in C, but I imagine it should be possible to manipulate them without
resorting to copying between haskell and C.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: hmatrix

2008-06-01 Thread Anatoly Yakovenko
do you have any plans to provide an interface for inplace updates?

On Sun, Jun 1, 2008 at 3:20 AM, Alberto Ruiz [EMAIL PROTECTED] wrote:
 Anatoly Yakovenko wrote:

 What is the most efficient way to update a position in a matrix or a
 vector?  I came up with this:

 updateVector :: Vector Double - Int - Double - Vector Double
 updateVector vec pos val = vec `add` v2
   where
  v2 = fromList $ (replicate (pos) 0.0) ++ ((val - (vec @
 pos)):(replicate ((dim vec)- pos - 1) 0.0))

 but this seems pretty inefficient to me.

 thanks,
 Anatoly


 It is probably more efficient to use subVector and join (implemented by
 copyArray):

 updateVector' v pos val
| pos == 0= join [b,c]
| pos == dim v -1 = join [a,b]
| otherwise   = join [a,b,c]
where a = subVector 0 pos v
  b = fromList [val]
  c = subVector (pos+1) (dim v -pos-1) v

 updateVector' (fromList [1,2,3,4,5]) 2 57
 5 | [1.0,2.0,57.0,4.0,5.0]

 (The three cases are required because empty vectors are not currently
 allowed.)

 Something similar can be done for matrices using flatten and reshape.

 Although vectors and matrices in this library are immutable and intended to
 be manipulated as a whole by higher level functions, this kind of update
 functions may often be useful. I will include them soon.

 Alberto

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


[Haskell-cafe] hmatrix

2008-05-31 Thread Anatoly Yakovenko
What is the most efficient way to update a position in a matrix or a
vector?  I came up with this:

updateVector :: Vector Double - Int - Double - Vector Double
updateVector vec pos val = vec `add` v2
   where
  v2 = fromList $ (replicate (pos) 0.0) ++ ((val - (vec @
pos)):(replicate ((dim vec)- pos - 1) 0.0))

but this seems pretty inefficient to me.

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


Re: [Haskell-cafe] hmatrix

2008-05-31 Thread Anatoly Yakovenko
http://perception.inf.um.es/~aruiz/darcs/hmatrix/doc/html/Data-Packed-Vector.html
provided by hmatrix

On Sat, May 31, 2008 at 3:20 PM, Thomas Hartman [EMAIL PROTECTED] wrote:
 what package do you install/import to get at Vector?

 2008/5/31 Thomas Hartman [EMAIL PROTECTED]:
 what package do you install/import to get at Vector?

 2008/5/31 Anatoly Yakovenko [EMAIL PROTECTED]:
 What is the most efficient way to update a position in a matrix or a
 vector?  I came up with this:

 updateVector :: Vector Double - Int - Double - Vector Double
 updateVector vec pos val = vec `add` v2
   where
  v2 = fromList $ (replicate (pos) 0.0) ++ ((val - (vec @
 pos)):(replicate ((dim vec)- pos - 1) 0.0))

 but this seems pretty inefficient to me.

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



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


[Haskell-cafe] fgl Data.Graph examples

2008-05-16 Thread Anatoly Yakovenko
Can someone post some simple examples of using the Data.Graph library?
So I can define a simple graph

let g = buildG (1,2) [(1,2), (2,1)]

but how do i label my edges and nodes?  i want to be able to name my
nodes, and add weights to the edges and be able to update those
weights as well.

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


Re: [Haskell-cafe] fgl Data.Graph examples

2008-05-16 Thread Anatoly Yakovenko
Thank you, that's exactly what i was looking for.


 I don't think there is a straightforward way to tweak individual nodes and
 edges other than using graph construction tools. Maybe someone could shed a
 light on this.

I think i can define updateEdge in terms of insEdge and delEdge
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ghc 6.8.2 and timer_create error

2008-03-19 Thread Anatoly Yakovenko
I have a gentoo box with ghc 6.8.2, and the binaries that ghc builds
on that box do not work on redhat EL 4 or ubuntu 7.10.  When I try to
run the binary, i get an error:

Main: timer_create: Invalid argument

so is there any way to get ghc to build a binary that doesn't use
timer_create?  or is that something that is configured when ghc itself
is built, if so, how do I turn that feature off?

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


Re: [Haskell-cafe] Re: [darcs-devel] announcing darcs 2.0.0pre3

2008-01-23 Thread Anatoly Yakovenko
i would recommend just using the native one.  The best performance
that I was able to get with ghc 6.6 was still seven times slower then
the native sha1 implementation.

2008/1/23 Peter Verswyvelen [EMAIL PROTECTED]:

  Maybe a dedicated SIMD version of SHA1?

  http://arctic.org/~dean/crypto/sha1.html

  Cheers,
  Peter


  David Roundy wrote:
  On Wed, Jan 23, 2008 at 03:26:51PM +, Simon Marlow wrote:


  There are still times when I see nothing happening, for example in the
 unpull test on the GHC repo (see previous messages), the last progress
 message I get is

 Reading patches in /64playpen/simonmar/ghc-darcs2 17040

 and it sits there for 7-8 seconds before completing. Does this maybe shed
 any light on why this unpull is 2 times slower than darcs1?

  I'm not entirely certain what's triggering this, but I have identified that
 removing a couple of sha1 checks cuts 1s out of 15s for me. This makes me
 wonder whether it's worth looking into a faster sha1 implementation.



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


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


[Haskell-cafe] can someone explain monad transformers to me, or how do you combine maybe and IO?

2007-11-12 Thread Anatoly Yakovenko
I wanted something that would work like liftM but with IO as well, so
something like this:

 liftM ((+) 1) $ Just 1
Just 2

but with the function lifted being of type (a - IO b).  so I came up with

maybeIO::(a - IO b) - (Maybe a - IO (Maybe b))
maybeIO ff = (\ aa -
   case aa of
  Nothing - return $ Nothing
  Just vv - do
 rv - ff vv
 return $ Just rv)

incIO:: Int - IO Int
incIO ii = return $ ii + 1


 maybeIO incIO $ Just 1
Just 2

works just like I want it to.  But isn't this something that a monad
transformer should be able to do?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: bizarre memory usage with data.binary

2007-10-03 Thread Anatoly Yakovenko
 ...and indeed it can't be done, except by the naive brute-force method
 of comparing every subtree, possibly optimized by cryptographically
 hashing a representation of every subtree, since sharing isn't an
 observable property.

i was thinking that instead of having a reference to a node, each node
just holds an index from an array of nodes.  Traversal would take an
extra step, but it should fix the problem with encode/decode.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] bizarre memory usage with data.binary

2007-10-02 Thread Anatoly Yakovenko
i am getting some weird memory usage out of this program:


module Main where

import Data.Binary
import Data.List(foldl')


main = do
   let sum' = foldl' (+) 0
   let list::[Int] = decode $ encode $ ([1..] :: [Int])
   print $ sum' list
   print done

it goes up to 500M and down to 17M on windows.  Its build with ghc
6.6.1 with the latest data.binary

Any ideas what could be causing the memory usage to jump around so much?


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


[Haskell-cafe] Re: bizarre memory usage with data.binary

2007-10-02 Thread Anatoly Yakovenko
Program1:

module Main where

import Data.Binary
import Data.List(foldl')


main = do
  let sum' = foldl' (+) 0
  let list::[Int] = decode $ encode $ ([1..] :: [Int])
  print $ sum' list
  print done

vs

Program2:

module Main where

import Data.Binary
import Data.List(foldl')


main = do
  let sum' = foldl' (+) 0
  let list::[Int] = [1..]
  print $ sum' list
  print done

neither program is expected to terminate.  The point of these examples
is to demonstrate that Data.Binary encode and decode have some strange
memory allocation patters.

If you run Program1, it will run forever, but its memory usage on my
machine goes to 500M then back down to 17M then back up to 500M then
back down to 17M... repeatedly.  I don't think this has anything to do
with running out of space in a 32 bit integer.

Program2 on the other hand runs at constant memory at around 2M.

Anatoly

On 10/2/07, Anatoly Yakovenko [EMAIL PROTECTED] wrote:
 i am getting some weird memory usage out of this program:


 module Main where

 import Data.Binary
 import Data.List(foldl')


 main = do
let sum' = foldl' (+) 0
let list::[Int] = decode $ encode $ ([1..] :: [Int])
print $ sum' list
print done

 it goes up to 500M and down to 17M on windows.  Its build with ghc
 6.6.1 with the latest data.binary

 Any ideas what could be causing the memory usage to jump around so much?


 Thanks,
 Anatoly

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


Re: [Haskell-cafe] Re: bizarre memory usage with data.binary

2007-10-02 Thread Anatoly Yakovenko
On 10/2/07, Don Stewart [EMAIL PROTECTED] wrote:
 aeyakovenko:
  Program1:
 
  module Main where
 
  import Data.Binary
  import Data.List(foldl')
 
 
  main = do
let sum' = foldl' (+) 0
let list::[Int] = decode $ encode $ ([1..] :: [Int])
print $ sum' list
print done

 The encode instance for lists is fairly strict:

 instance Binary a = Binary [a] where
 put l  = put (length l)  mapM_ put l
 get= do n - get :: Get Int
 replicateM n get

 This is ok, since typically you aren't serialising infinite structures.

hmm, this doesn't make sense to me, it goes up to 500M then down then
back up, then back down, so it doesn't just run out of memory because
of (length l) forces you to evaluate the entire list.

 Use a newtype, and a lazier instance, if you need to do this.

Thanks for the tip.  this runs at a constant 4M

module Main where

import Data.Binary
import Data.List(foldl')

data Foo = Foo Int Foo | Null

instance Binary Foo where
   put (Foo i f) = do put (0 :: Word8)
  put i
  put f
   put (Null)  = do put (1 :: Word8)
   get = do t - get :: Get Word8
case t of
   0 - do i - get
   f - get
   return (Foo i f)
   1 - do return Null

sumFoo zz (Null) = zz
sumFoo zz (Foo ii ff) = sumFoo (zz + ii) ff

fooBar i = Foo i (fooBar (i + 1))

main = do
   print $ sumFoo 0 $ decode $ encode $ fooBar 1
   print done
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: bizarre memory usage with data.binary

2007-10-02 Thread Anatoly Yakovenko
servers never terminate, pretend that i have a server that reads a
list encoded with data.binary from a socket, and sums it up and
returns the current sum.  i would expect it to run in constant memory,
never terminate, and do useful work.

which is basically the problem that I am facing right now.  my program
seems to grow randomly in memory use when marshaling large data types
encoded using data.binary.

On 10/2/07, Dan Weston [EMAIL PROTECTED] wrote:
 Maybe what you are observing is that the operational semantics of
 undefined is undefined. The program can halt, run forever, use no
 memory, use all the memory.

 Although I doubt what GHC does with this code is a random process, I
 don't think it's too meaningful to ask what are the space usage patterns
 of a program returning bottom.

 Anatoly Yakovenko wrote:
  Program1:
 
  module Main where
 
  import Data.Binary
  import Data.List(foldl')
 
 
  main = do
let sum' = foldl' (+) 0
let list::[Int] = decode $ encode $ ([1..] :: [Int])
print $ sum' list
print done
 
  vs
 
  Program2:
 
  module Main where
 
  import Data.Binary
  import Data.List(foldl')
 
 
  main = do
let sum' = foldl' (+) 0
let list::[Int] = [1..]
print $ sum' list
print done
 
  neither program is expected to terminate.  The point of these examples
  is to demonstrate that Data.Binary encode and decode have some strange
  memory allocation patters.
 
  If you run Program1, it will run forever, but its memory usage on my
  machine goes to 500M then back down to 17M then back up to 500M then
  back down to 17M... repeatedly.  I don't think this has anything to do
  with running out of space in a 32 bit integer.
 
  Program2 on the other hand runs at constant memory at around 2M.
 
  Anatoly
 
  On 10/2/07, Anatoly Yakovenko [EMAIL PROTECTED] wrote:
  i am getting some weird memory usage out of this program:
 
 
  module Main where
 
  import Data.Binary
  import Data.List(foldl')
 
 
  main = do
 let sum' = foldl' (+) 0
 let list::[Int] = decode $ encode $ ([1..] :: [Int])
 print $ sum' list
 print done
 
  it goes up to 500M and down to 17M on windows.  Its build with ghc
  6.6.1 with the latest data.binary
 
  Any ideas what could be causing the memory usage to jump around so much?
 
 
  Thanks,
  Anatoly
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 



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


Re: [Haskell-cafe] Re: bizarre memory usage with data.binary

2007-10-02 Thread Anatoly Yakovenko
 If its specifically the list instance, where we currently trade laziness
 for efficiency of encoding (which may or may not be the right thing),
 I'd suggest a fully lazy encoding instance?

Its not really a list, its more of a tree that has shared nodes, so
something like this:

A
 / \
B  C
  \   /
   D
 /   \
EF

I suspect that maybe after encode/decode i end up with something like

A
 / \
B  C
   /  \
  D   D
 /   \/   \
EFE F
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] trying to install gutsy's libghc6-mtl-dev from source on feisty

2007-08-31 Thread Anatoly Yakovenko
yea, i built the deb from gutsy's deb-src repository using apt-get source
--build.  i am trying to figure out why that deb that i build doesn't work

On 8/31/07, Thomas Hartman [EMAIL PROTECTED] wrote:


 you may want to generate the .deb rather than take the deb that was
 packaged for gutsy.

 http://www.haskell.org/pipermail/haskell-cafe/2007-April/024137.html

 pupeno's guide to do this:

 http://pupeno.com/2006/12/17/unstable-packages-on-ubuntu/




  *Anatoly Yakovenko [EMAIL PROTECTED]*
 Sent by: [EMAIL PROTECTED]

 08/31/2007 01:42 PM
   To
 haskell-cafe@haskell.org  cc
   Subject
 [Haskell-cafe] trying to install gutsy's libghc6-mtl-dev from
  source on feisty




 i have ghc6_6.6.1-2ubuntu2_i386.deb and
 ghc6-prof_6.6.1-2ubuntu2_i386.deb installed, but i cant seem to get
 mtl to install, can someone tell me what this output means?   i just
 switched to a debian based system from gentoo, so i dont grok dpkg
 yet:

 [EMAIL PROTECTED]:~$ sudo dpkg -i libghc6-mtl-dev_1.0.1-2_i386.deb
 (Reading database ... 129709 files and directories currently installed.)
 Preparing to replace libghc6-mtl-dev 1.0-3 (using
 libghc6-mtl-dev_1.0.1-2_i386.deb) ...
 ghc-pkg: cannot find package mtl-1.0
 dpkg: warning - old pre-removal script returned error exit status 1
 dpkg - trying script from the new package instead ...
 ghc-pkg: cannot find package mtl-1.0
 dpkg: error processing libghc6-mtl-dev_1.0.1-2_i386.deb (--install):
 subprocess new pre-removal script returned error exit status 1
 Reading package info from stdin ... done.
 ghc-pkg: dependency base-2.0 doesn't exist (use --force to override)
 dpkg: error while cleaning up:
 subprocess post-installation script returned error exit status 1
 Errors were encountered while processing:
 libghc6-mtl-dev_1.0.1-2_i386.deb
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


 ---

 This e-mail may contain confidential and/or privileged information. If you

 are not the intended recipient (or have received this e-mail in error)
 please notify the sender immediately and destroy this e-mail. Any
 unauthorized copying, disclosure or distribution of the material in this
 e-mail is strictly forbidden.

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


  1   2   >