[Haskell-cafe] Render fonts in HopenGL

2011-02-26 Thread er9999
Hello,
 Can anyone give me an example for fonts rendering? I tried to use FTGL 
library, but it is too complicated on Windows(compile). Is it possible to do it 
in a simple way? I need more than the given example in red book(Font.hs), 
something like outline font. By the way, I am new in OpenGL and Haskell, so the 
real exmaple should be the best. Thanks! 

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


Re: [Haskell-cafe] why is ghci trying to load hsc file ??

2011-02-26 Thread Chris Smith
On Sat, 2011-02-26 at 21:36 -0800, bri...@aracnet.com wrote:
> [1 of 2] Compiling Bindings.HDF5( dist/build/Bindings/HDF5.hs,
> interpreted ) *** Parser:
> 
> src/Bindings/HDF5.hsc:49:8: parse error on input `import'

So it's in HDF5.hs ultimately, but LINE directives are telling it to
report a different location.

> HDF5.hs file has LINE scattered throughout, but they are in comments:
> 
> {-# LINE 15 "src/Bindings/HDF5.hsc" #-}

Those {-# ... #-} things are pragmas.  As far as the language spec goes
they are comments, but actually, compilers read them and interpret their
contents.  In this case, it causes the compiler to report a different
location for errors.

> regardless, there is NO "LINE 49" directive, and the HDF5.hs file is
> blank on line 49.

Line 49 of HDF5.hs doesn't matter.  What's on line 49 of the hsc file?

If you don't want to debug using the hsc file (which is the way this is
designed), you'll have to find the LINE directive in the .hs file
nearest to (but before) 49, and count lines from there.

-- 
Chris Smith


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


Re: [Haskell-cafe] why is ghci trying to load hsc file ??

2011-02-26 Thread briand
On Sat, 26 Feb 2011 18:18:27 -0800 (PST)
Brandon Moore  wrote:

> I assume there's a LINE directive in the file it's actually reading.
> Run ghci with -v to see what file it's actually trying to read.
> 
> 
>   

Here's the relevant output with -v flag:


compile: input file dist/build/Bindings/HDF5.hs
*** Checking old interface for main:Bindings.HDF5:
[1 of 2] Compiling Bindings.HDF5( dist/build/Bindings/HDF5.hs,
interpreted ) *** Parser:

src/Bindings/HDF5.hsc:49:8: parse error on input `import'


This is very weird.

HDF5.hs file has LINE scattered throughout, but they are in comments:

{-# LINE 15 "src/Bindings/HDF5.hsc" #-}

or are they ?  I assumed the purpose of this was line # annotation to
let you know where the line in the .hs file comes from in the .hsc
file.

regardless, there is NO "LINE 49" directive, and the HDF5.hs file is
blank on line 49.

The first line with import (@ 165) is this :

foreign import ccall "H5Dcreate2" c'H5Dcreate2
  :: CInt -> CString -> CInt -> CInt -> CInt -> CInt -> CInt -> IO

I'm trying to figure out if that's legal syntax.

Very strange.  Reporting errors on lines that don't exist makes it
harder to debug :-(

Brian

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


Re: [Haskell-cafe] why is ghci trying to load hsc file ??

2011-02-26 Thread Brandon Moore
I assume there's a LINE directive in the file it's actually reading.
Run ghci with -v to see what file it's actually trying to read.


  

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


[Haskell-cafe] why is ghci trying to load hsc file ??

2011-02-26 Thread briand
Howdy,

I worked out a small hdf5 binding using cabal and bindings-DSL and
sqlite3 as my example.

Time to try it !

ghci -idist/build/ dist/build/Bindings/HDF5.o -lhdf5 -lhdf5_hl
hdf5_pkg_test.hs


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 object (static) dist/build/Bindings/HDF5.o ... done
Loading object (dynamic) hdf5 ... done
Loading object (dynamic) hdf5_hl ... done
final link ... done
[1 of 2] Compiling Bindings.HDF5( dist/build/Bindings/HDF5.hs,
interpreted )

src/Bindings/HDF5.hsc:49:8: parse error on input `import'
Failed, modules loaded: none.


Huh ?  Why is it trying to read HDF5.hsc ??  What's even more
interesting is that line 49 of that file doesn't have an import on it,
so something is fubar.

No idea how this could be happening.  I've included a copy of my cabal
file.

BTW. I have to specify the hdf5 libraries, i.e. libhdf5 and libhdf5_hl
on the command line. It seems like the build process should have taken
care of that in some way, maybe... ?  Certainly when I use something
like sqlite3, I'm not specifying libsqlite3 on the command line.

Thanks,

Brian


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


Re: [Haskell-cafe] Type problem

2011-02-26 Thread michael rice
Yeah, my bad.

Thanks.

Michael

--- On Sat, 2/26/11, Stephen Tetley  wrote:

From: Stephen Tetley 
Subject: Re: [Haskell-cafe] Type problem
To: 
Cc: haskell-cafe@haskell.org
Date: Saturday, February 26, 2011, 3:24 PM

Does this help?

listbind :: [a] -> (a -> [b]) -> [b]
listbind = (>>=)

___
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] Type problem

2011-02-26 Thread Stephen Tetley
Does this help?

listbind :: [a] -> (a -> [b]) -> [b]
listbind = (>>=)

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


Re: [Haskell-cafe] Type problem

2011-02-26 Thread Thomas Davie
Because applying f to the list is not the same thing is applying bind to the 
list and f.

Bob

On 26 Feb 2011, at 20:17, michael rice wrote:

> Why? Shouldn't this work for any type a?
> 
> Michael
> 
> ==
> 
> f :: [a] -> [a]
> f l = do x <- l
>  return x
> 
> ==
> 
> *Main> :r
> [1 of 1] Compiling Main ( test.hs, interpreted )
> Ok, modules loaded: Main.
> *Main> f "abcde"
> "abcde"
> *Main> f [1,2,3,4,5]
> [1,2,3,4,5]
> *Main> "abcde" >>= f
> 
> :1:12:
> Couldn't match expected type `Char' against inferred type `m b'
> In the second argument of `(>>=)', namely `f'
> In the expression: "abcde" >>= f
> In the definition of `it': it = "abcde" >>= f
> *Main> 
> 
> 
> ___
> 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] Type problem

2011-02-26 Thread michael rice
Why? Shouldn't this work for any type a?

Michael

==

f :: [a] -> [a]
f l = do x <- l
 return x

==

*Main> :r
[1 of 1] Compiling Main ( test.hs, interpreted )
Ok, modules loaded: Main.
*Main> f "abcde"
"abcde"
*Main> f [1,2,3,4,5]
[1,2,3,4,5]
*Main> "abcde" >>= f

:1:12:
    Couldn't match expected type `Char' against inferred type `m b'
    In the second argument of `(>>=)', namely `f'
    In the expression: "abcde" >>= f
    In the definition of `it': it = "abcde" >>= f
*Main> 




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


Re: [Haskell-cafe] Simulating open datatypes with type families?

2011-02-26 Thread Stephen Tetley
I don't think typeclasses or a type family will solve the problem directly.

Both the statement parsers are producing concrete types - type class
polymorphism won't be able to create a union of the two concrete types
- a concrete sum type (i.e. Either) will be able to make the union,
but it would make the grammar messy.

Making an extensible parser for a language as big as C will be tricky.
Tim Sheard and Emir Pasalic have done it for a small language in this
paper - they use a technique that doubles the number of constructors.

http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.19.8983

Best wishes

Stephen

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


Re: [Haskell-cafe] Auto elimination of MVars using a monad or monad transformer.

2011-02-26 Thread Ryan Ingram
You might want to take a look at
http://hackage.haskell.org/package/Adaptivesince it seems really
similar to what you are trying to do.  In fact, you
might also want to google 'Functional Reactive Programming'.

  -- ryan

On Thu, Feb 24, 2011 at 10:41 PM, Chris Dew  wrote:

> Hello, just like everyone else, I have a question about monads.  I've
> read the tutorials, written one monad myself (not in this email), but
> I still consider myself a Haskell beginner.
>
> * Does GHC eliminate unneeded MVars during compilation?
>
> I'm expecting that it doesn't, as that would mean optimising away
> ForkIOs, which would be quite a thing to do.  I've included example
> code below.
>
> * Is there a monad which allows their automatic elimination of MVars
> (or their creation only when necessary)?
>
> This would be similar to how the IO monad allows you to do purely
> functional things with a do block, using let.
>
> I've had a go at a lifting function, which wraps a pure function into
> an IO action which forever reads from one MVar and writes to another.
> What I'm looking for is some form of Monadic context in which many
> pure functions, MVar fillers and MVar consumers could be linked
> together, where only the necessary MVars remain (or were created) at
> compilation time.
>
> * Would this be a monad, or a monad transformer?
>
> * Can you specialise a monad transformer on a single base (in this
> case IO) so that you can use forkIO in the bind or return?
>
> Thanks,
>
> Chris.
>
>
> module Main (
> main
> )
> where
>
> import Control.Concurrent (forkIO, MVar, newEmptyMVar, putMVar,
> takeMVar, ThreadId, threadDelay)
> import Control.Monad (forever)
>
> stepA :: MVar String -> IO ()
> stepA boxa = forever $ do
>  line <- getLine
>  putMVar boxa line
>
> stepB :: MVar String -> IO ()
> stepB boxb = forever $ do
>  line <- takeMVar boxb
>  putStrLn line
>
> -- This simply wraps a string in brackets.
> bracket :: String -> String
> bracket x = "(" ++ x ++ ")"
>
> -- This lifts a function into an action which forever performs the function
> -- between the two MVars given.
> lft :: (a -> b) -> MVar a -> MVar b -> IO ()
> lft f c d = forever $ do
> x <- takeMVar c
> putMVar d (f x)
>
> -- Just like C's main.
> main :: IO ()
> main = do
>  box <- newEmptyMVar
>  box2 <- newEmptyMVar
>  forkIO $ stepA box
>  forkIO $ lft bracket box box2
>  forkIO $ stepB box2
>  threadDelay 1000 -- Sleep for at least 10 seconds before exiting.
>
> ___
> 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] Simulating open datatypes with type families?

2011-02-26 Thread Patrick Thomson
I'm currently working on a project that involves a C parser (using Parsec3) 
that needs to be dynamically extensible - i.e. end-users should be able to add 
new statement types, expression types, operators, and so on and so forth.

Since Haskell ADT's are closed, I thought I would be able to simulate this by 
using type families, e.g.:

{-# LANGUAGE TypeFamilies, DeriveDataTypeable #-}

-- the statement type
type CStatement = BreakStmt
   | CaseStmt CExpression CStatement
-- rest of the statement types omitted here for brevity
-- CStatement derives (Show, Eq, Typeable, Data)

statement :: Parser CStatement
-- how exactly this is parsed is not relevant, so its definition is also omitted

data family StatementLike a
data instance StatementLike CStatement = MkStmt CStatement

-- okay, this is all well and good. let's create a new ADT, representing the 
Ruby/Perl-esque 'until' statement and add a StatementLike instance for it.

data Until = UntilStmt CExpression CStatement deriving (Eq, Show, Typeable, 
Data)
data instance StatementLike Until = MkUntil Until

untilStatement :: Parser Until
-- definition omitted

-- Here's where it breaks down. I want to be able to have a function of type 
Parser (StatementLike a) so that I can pattern-match over the a in future code, 
but this function doesn't typecheck: GHC says that the function can't be that 
general - it expects either a Parser (StatementLike CStatement) or a Parser 
(StatementLike Until).
newStatement :: Parser (CStatement a)
newStatement = (MkUntil <$> untilStatement) <|> (MkStmt <$> statement)

Am I expecting the wrong thing of type families? Are typeclasses the better way 
to do this? Is there any other way to simulate an open, extensible ADT, or am I 
totally barking up the wrong tree?

Any assistance would be much appreciated. Please let me know if I need to 
provide more information.

Thanks in advance,
-- Patrick Thomson
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell platform installation failure on OS X 10.6.6 (intel)

2011-02-26 Thread Mark Lentczner
This should be fixed in the next (2011) Haskell Platform. You should receive
"Please install Xcode developer tools first."

- Mark

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


Re: [Haskell-cafe] Haskell Platform install instructions

2011-02-26 Thread Mark Lentczner
> * Should we document this somewhere in the Haskell Platform install
> process? I'm sure many old-time users of cabal are well aware that
> they need ~/.cabal/bin in the PATH, but new users will not be.

In the next version of Haskell Platform, on Mac OS X, happy will be installed 
with the other platform files, and symlink'd into /usr/bin.

> The need to mention ~/.cabal/bin belongs to the empty user guide of 
> cabal-install.

I'm not sure what is meant by "guide" here.  cabal-install has a symlink-bindir 
option. In the next version of Haskell Platform, on Mac OS X, if the user has 
no ~/.cabal directory at all, then I'm planning on having it install a 
~/.cabal/config file that, among other things, will set this symlink-bindir to 
symlink into ~/bin.

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


Re: [Haskell-cafe] FFI: C-side object not destructed

2011-02-26 Thread Daniel Fischer
On Saturday 26 February 2011 13:53:41, Maciej Marcin Piechotka wrote:
> It is implementation defined (so not "C++" but " implementation>".

IIRC, it's not even that, but undefined behaviour.

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


Re: [Haskell-cafe] FFI: C-side object not destructed

2011-02-26 Thread Maciej Marcin Piechotka
On Sat, 2011-02-26 at 14:22 +0300, Miguel Mitrofanov wrote:
> Well, this code in C++ would probably work too:
> 
> Klass *k = new Klass(4,5);
> delete k;
> std::cout << k->getY() << std::endl;
> 
> though smart compiler would probably issue a warning. See, when you
> delete something, C++ doesn't automagically mark your pointer as
> "invalid"; in fact, it preserves all the data in your deleted class.
> If you didn't provide a destructor, then the only outcome of "delete"
> would be that the same memory can be assigned to another object by
> "new" operator, but it doesn't get cleared or invalidated in any way.
> 
> Seems to me, Haskell works in the same way. 

It is implementation defined (so not "C++" but "".

% cat test.cc 
#include 

int main() {
int *i = new int(4);
std::cout << *i << std::endl;
delete i;
std::cout << *i << std::endl;
}
% g++ test.cc
% ./a.out 
4
0

I believe that crash in 4th line is legal as well.

Regards



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


Re: [Haskell-cafe] FFI: C-side object not destructed

2011-02-26 Thread Yves Parès
I assume you are right.
The weirdest thing here is that getY() returns the Y value of the destructed
object while getX() returns always 0.


2011/2/26 Miguel Mitrofanov 

> Well, this code in C++ would probably work too:
>
> Klass *k = new Klass(4,5);
> delete k;
> std::cout << k->getY() << std::endl;
>
> though smart compiler would probably issue a warning. See, when you delete
> something, C++ doesn't automagically mark your pointer as "invalid"; in
> fact, it preserves all the data in your deleted class. If you didn't provide
> a destructor, then the only outcome of "delete" would be that the same
> memory can be assigned to another object by "new" operator, but it doesn't
> get cleared or invalidated in any way.
>
> Seems to me, Haskell works in the same way.
>
> On 26 Feb 2011, at 13:59, Yves Parès wrote:
>
> > Hello,
> > I'm trying to use a C++ class in Haskell through C exports.
> > It works all very well, except that when I call the function that deletes
> the object, it is still valid, I can still call methods on it.
> >
> > Here is my Haskell code:
> >
> > {-# LANGUAGE ForeignFunctionInterface #-}
> >
> > import Foreign
> > import Foreign.C.Types
> >
> > newtype PKlass = PKlass (Ptr PKlass)
> >
> > foreign import ccall unsafe "Klass_Create"
> >   kCreate :: CInt -> CInt -> IO PKlass
> >
> > foreign import ccall unsafe "Klass_Destroy"
> >   kDestroy :: PKlass -> IO ()
> >
> > foreign import ccall unsafe "Klass_GetX"
> >   kGetX :: PKlass -> IO CInt
> > foreign import ccall unsafe "Klass_GetY"
> >   kGetY :: PKlass -> IO CInt
> >
> > foreign import ccall unsafe "Klass_AddKlass"
> >   kAdd :: PKlass -> PKlass -> IO PKlass
> >
> >
> > main = do
> >   k <- kCreate 4 5
> >   kDestroy k
> >   kGetY k >>= print   -- This shouldn't work
> >   k' <- kCreate 2 8
> >   k'' <- k `kAdd` k'
> >   kDestroy k''
> >   kGetY k'' >>= print   -- This neither
> >
> >
> > So it is very basic, and I can't understand why the supposedly destroyed
> objects are still here.
> > Enclosed is all the source code (C++ class, C exportation and the Haskell
> main hereabove).
> >
> > I compile it this way:
> > ghc --make main.hs *.cpp -lstdc++
> > ___
> > 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] Either instance of Monad?

2011-02-26 Thread Yves Parès
I tried reinstalling GHC 7.0.1 from scratch, the issue remains...


2011/2/26 Daniel Fischer 

> On Saturday 26 February 2011 12:54:02, Yves Parès wrote:
> > When I look at the documentation of Control.Monad.Error [1] or
> > Control.Applicative [2] it is not said that it re-exports
> > Control.Monad.Instances. So maybe this behaviour is normal...
>
> I don't think so. Instances are automatically propagated, they can't be
> hidden once they're in scope. Functor, Monad, Either and (->) are all
> available in the Prelude, so unless you have NoImplicitPrelude, the
> instances ought to be in scope from any transitive dependency.
> And they are in scope for me when I import Control.Monad.Error or
> Control.Applicative, so something is amiss if they're not in scope for you.
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Either instance of Monad?

2011-02-26 Thread Daniel Fischer
On Saturday 26 February 2011 12:54:02, Yves Parès wrote:
> When I look at the documentation of Control.Monad.Error [1] or
> Control.Applicative [2] it is not said that it re-exports
> Control.Monad.Instances. So maybe this behaviour is normal...

I don't think so. Instances are automatically propagated, they can't be 
hidden once they're in scope. Functor, Monad, Either and (->) are all 
available in the Prelude, so unless you have NoImplicitPrelude, the 
instances ought to be in scope from any transitive dependency.
And they are in scope for me when I import Control.Monad.Error or 
Control.Applicative, so something is amiss if they're not in scope for you.

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


Re: [Haskell-cafe] Either instance of Monad?

2011-02-26 Thread Yves Parès
When I look at the documentation of Control.Monad.Error [1] or
Control.Applicative [2] it is not said that it re-exports
Control.Monad.Instances. So maybe this behaviour is normal...

[1]
http://hackage.haskell.org/packages/archive/mtl/2.0.1.0/doc/html/Control-Monad-Error.html
[2]
http://hackage.haskell.org/packages/archive/base/4.3.0.0/doc/html/Control-Applicative.html


2011/2/24 Yves Parès 

> I have the same problem with instances of Functor.
> For instance when I import Control.Applicative, to get the instance
> "Functor ((->) a)" I also have to import Control.Monad.Instances.
>
>
> 2011/2/23 Daniel Fischer :
> > On Wednesday 23 February 2011 14:14:46, Yves Parès wrote:
> >> The latest, I think :
> >> GHC 7.0.1,
> >> mtl-2.0.1.0,
> >> base-4.3.0.0
> >
> > Hmm, that's exactly what I have. Weirder and weirder.
> > For the moment, I'm out of ideas.
> >
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FFI: C-side object not destructed

2011-02-26 Thread Miguel Mitrofanov
Well, this code in C++ would probably work too:

Klass *k = new Klass(4,5);
delete k;
std::cout << k->getY() << std::endl;

though smart compiler would probably issue a warning. See, when you delete 
something, C++ doesn't automagically mark your pointer as "invalid"; in fact, 
it preserves all the data in your deleted class. If you didn't provide a 
destructor, then the only outcome of "delete" would be that the same memory can 
be assigned to another object by "new" operator, but it doesn't get cleared or 
invalidated in any way.

Seems to me, Haskell works in the same way.

On 26 Feb 2011, at 13:59, Yves Parès wrote:

> Hello,
> I'm trying to use a C++ class in Haskell through C exports.
> It works all very well, except that when I call the function that deletes the 
> object, it is still valid, I can still call methods on it.
> 
> Here is my Haskell code:
> 
> {-# LANGUAGE ForeignFunctionInterface #-}
> 
> import Foreign
> import Foreign.C.Types
> 
> newtype PKlass = PKlass (Ptr PKlass)
> 
> foreign import ccall unsafe "Klass_Create"
>   kCreate :: CInt -> CInt -> IO PKlass
> 
> foreign import ccall unsafe "Klass_Destroy"
>   kDestroy :: PKlass -> IO ()
> 
> foreign import ccall unsafe "Klass_GetX"
>   kGetX :: PKlass -> IO CInt
> foreign import ccall unsafe "Klass_GetY"
>   kGetY :: PKlass -> IO CInt
> 
> foreign import ccall unsafe "Klass_AddKlass"
>   kAdd :: PKlass -> PKlass -> IO PKlass
> 
> 
> main = do
>   k <- kCreate 4 5
>   kDestroy k
>   kGetY k >>= print   -- This shouldn't work
>   k' <- kCreate 2 8
>   k'' <- k `kAdd` k'
>   kDestroy k''
>   kGetY k'' >>= print   -- This neither
> 
> 
> So it is very basic, and I can't understand why the supposedly destroyed 
> objects are still here.
> Enclosed is all the source code (C++ class, C exportation and the Haskell 
> main hereabove).
> 
> I compile it this way:
> ghc --make main.hs *.cpp -lstdc++
> ___
> 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] Fun with the ST monad

2011-02-26 Thread Stephen Tetley
Hi wren

Thanks for that explanation - it's by far the clearest description of
iteratees / enumerators I've seen.

Best wishes

Stephen

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


Re: [Haskell-cafe] Fun with the ST monad

2011-02-26 Thread Kevin Quick

In part to help solidify my own understanding and usage, I wrote up
the following which shows a comparison of processing an input file.
Andrew Coppin originally posed the issue concerning strictness imposed
by using the ST monad for processing an input file.

This literate example shows a comparison of processing a file using:
   1. the ST monad
   2. the ST monad with Luke Palmer's suggested laziness
   3. the State monad
   4. a direct Iteratee (from John Millikin's Enumerator package)
   5. the same Iteratee in Monad form
   6. another slight variation of the Iteratee in Monad form


First, lets get the basics taken care of:


import System.IO
import System.Environment
import Data.Word
import Data.Bits
import qualified Data.ByteString as B
import Control.Applicative ( (<$>) )
import Control.Monad.Trans.Class (lift)
import Control.Monad.IO.Class
import Control.Monad.ST.Lazy
import Data.STRef.Lazy
import Control.Monad.Trans.State.Lazy
import qualified Data.Enumerator as E
import Data.Enumerator ( ($$) )
import qualified Data.Enumerator.Binary as EB
import qualified Data.Enumerator.List as EL


This example is intended to show the effects of lazy or strict
processing of a file, so an input file is needed.


inp = "input.example"


This input file can contain whatever you'd like, but for my testing I

simply created a 5MB file of zeros via:

   $ dd if=/dev/zero of=input.example count=1
   $ ls -sh input.example
   4.9M input.example

The output file will use the following base name, with the number of
the processing mode appended.


oup = "output.example"


The stats output of ghc will be used to compare the different
processing modes, so only one process will be performed each time the
application is run.  The processing mode desired will be input as a
command-line parameter, defaulting to the first mode.


main = do tna <- getArgs
  let tn = read $ head $ tna ++ ["1"]
  case tn of
6 -> testE 6 transform6
5 -> testE 5 transform5
4 -> testE 4 transform4
3 -> testT 3 transform3
2 -> testT 2 transform2
_ -> testT 1 transform1


To build and run this example (assuming this literate source is saved
as fproc.lhs):

  $ ghc -o fproc --make fproc.lhs && for N in $(seq 1 5) ; do time ./fproc $N 
+RTS -t -RTS ; done


That's all the basic setup out of the way.

The actual processing of the file is irrelevant other than needing to
remember previous input to process the current input.  In my example
each byte is usually combined with the previous byte to determine the
output byte.  In the ST and State monad forms, the previous byte value
is stored in the state portion of the monad.

The ST form is my interpretation of Andrew's original intent.


transform1 xs = runST (newSTRef 0 >>= work xs)



where work [] _ = return []
  work (e:es) s = do n <- readSTRef s
 writeSTRef s $ shiftR e 4
 let r = if e < 32 then e else n+e
 (r :) <$> work es s


To run this with standardized file processing, ByteString -> Word8
conversion, and output, main uses the testT wrapper.  Hopefully all
the pack and unpack operations are fusing and I haven't skewed the
results by introducing strictness at this level.


testT n t = let oun = oup ++ show n
op = B.pack . t . B.unpack
in print n >> op <$> B.readFile inp >>= B.writeFile oun


My output from this is:

./fproc 1 +RTS -t
1
<>

real0m14.998s
user0m13.650s
sys 0m1.333s

This is a processing rate of about 333KB/s, and memory consumption is
quite high, despite lazy processing.  Note that this is GHC 6.12.3, so
it doesn't have the IO performance updates present in 7.x.

Just to verify that there was laziness, I changed the imports from
Control.Monad.ST.Lazy and Data.STRef.Lazy to the .Strict versions and
got this:

./fproc 1 +RTS -t
1
Stack space overflow: current size 8388608 bytes.
Use `+RTS -Ksize -RTS' to increase it.
<>

real0m10.351s

user0m9.865s
sys 0m0.455s


Luke Palmer recommended some laziness techniques.  Notably I think he
added strictness to the STRef update value computation and used fmap
(x:) to yield a value prior to the recursion.  I don't know if the
latter is also achieved by Applicative's <$> that I used above, but
here is the updated version:


transform2 xs = runST (newSTRef 0 >>= work xs)
where work [] _ = return []
  work (e:es) s = do n <- readSTRef s
 writeSTRef s $! shiftR e 4
 let r = if e < 32 then e else n+e
 fmap (r :) $ work es s



This yields nearly identical results (actually slightly worse, but
that may be within the measuring variance):

./fproc 2 +RTS -t
2
<>

real0m15.378s
user0m13.985s
sys 0m1.346s


And just to verify that the performance is not unique to the ST monad,
here's the same thing with the State m