[Haskell-cafe] PhD student on Real-life datatype-generic programming

2007-06-13 Thread Johan Jeuring
=== Vacancy PhD student on Real-life datatype-generic programming Software Technology, Utrecht University, The Netherlands. === Within the Software Technology group of the Information and Computing

Re: [Haskell-cafe] How to devide matrix into small blocks

2007-06-13 Thread Janis Voigtlaender
L.Guo wrote: Hi all: I already have one matrix of type [[a]] to store one image. What I want to do is to devide the image into severial small blocks in same size. In the sense of dividing an image like abcd efgh ijkl mnop into the sequence of images [ ab ef , cd gh , ij mn , kl op ]

Re: [Haskell-cafe] How to devide matrix into small blocks

2007-06-13 Thread Janis Voigtlaender
Henning Thielemann wrote: On Wed, 13 Jun 2007, L.Guo wrote: I already have one matrix of type [[a]] to store one image. What I want to do is to devide the image into severial small blocks in same size. To do that, I wrote this tool function. chop :: Int - [a] - [[a]] chop _ [] = []

Re: [Haskell-cafe] How to devide matrix into small blocks

2007-06-13 Thread Henning Thielemann
On Wed, 13 Jun 2007, L.Guo wrote: I already have one matrix of type [[a]] to store one image. What I want to do is to devide the image into severial small blocks in same size. To do that, I wrote this tool function. chop :: Int - [a] - [[a]] chop _ [] = [] chop n ls = take n ls :

[Haskell-cafe] Re: [Haskell] ANNOUNCE: Harpy -- run-time code generation library

2007-06-13 Thread Martin Grabmueller
[Moved to haskell-cafe] Daniel Mahler schrieb: Given your reservation regarding LLVM, you may be interested in vmgen, developed and used as a part of gforth. It is also claimed that a JVM built with vmgen had performance comparable to state of the art JITs. If I remember the author of both

[Haskell-cafe] Re: Construct all possible trees

2007-06-13 Thread apfelmus
Andrew Coppin wrote: I'm trying to construct a function all_trees :: [Int] - [Tree] such that all_trees [1,2,3] will yield [ Leaf 1, Leaf 2, Leaf 3, Branch (Leaf 1) (Leaf 2), Branch (Leaf 1) (Leaf 3), Branch (Leaf 2) (Leaf 1), Branch (Leaf 2) (Leaf 3), Branch (Leaf 3) (Leaf 1),

[Haskell-cafe] Re: [Haskell] Who pays for *.haskell.org machines?

2007-06-13 Thread Bulat Ziganshin
Hello Malcolm, Wednesday, June 13, 2007, 1:55:43 PM, you wrote: In addition, we are in the process of setting up a separate server called code.haskell.org thank you, it's all are great news. some questions: when you plan to make code.haskell.org available? is its funding will be

[Haskell-cafe] Re: [Haskell] Who pays for *.haskell.org machines?

2007-06-13 Thread Malcolm Wallace
In addition, we are in the process of setting up a separate server called code.haskell.org when you plan to make code.haskell.org available? When it is ready. Wait for further announcements. is its funding will be reliable? for example, if we don't get money from Google in 2008

Re: [Haskell-cafe] Construct all possible trees

2007-06-13 Thread Mirko Rahn
Andrew Coppin wrote: such that all_trees [1,2,3] will yield [ Leaf 1, Leaf 2, Leaf 3, Branch (Leaf 1) (Leaf 2), Branch (Leaf 1) (Leaf 3), Branch (Leaf 2) (Leaf 1), Branch (Leaf 2) (Leaf 3), Branch (Leaf 3) (Leaf 1), Branch (Leaf 3) (Leaf 2), Branch (Branch (Leaf 1) (Leaf 2)) (Leaf 3), Branch

[Haskell-cafe] Construct all possible trees

2007-06-13 Thread Tom Pledger
*Andrew Coppin wrote: * | I'm trying to construct a function | | all_trees :: [Int] - [Tree] | | such that all_trees [1,2,3] will yield : If you write a helper function that takes an N element list, and returns all 2^N ways of dividing those elements into 2 lists, e.g. splits ab --

Re: [Haskell-cafe] Construct all possible trees

2007-06-13 Thread Henning Thielemann
On Thu, 14 Jun 2007, Tom Pledger wrote: *Andrew Coppin wrote: * | I'm trying to construct a function | | all_trees :: [Int] - [Tree] | | such that all_trees [1,2,3] will yield : If you write a helper function that takes an N element list, and returns all 2^N ways of dividing

Re: [Haskell-cafe] Re: Construct all possible trees

2007-06-13 Thread Mirko Rahn
apfelmus wrote: Explanation and the code: import Data.List import Control.Applicative import qualified Data.Foldable as Foldable import Data.Traversable as Traversable import Control.Monad.State data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving (Show)

[Haskell-cafe] Redefining Disjunction

2007-06-13 Thread PR Stanley
Hi Can you think of a fourth way of redefining disjunct using pattern matching? vee :: Bool - Bool - Bool vee _ True = True vee True _ = True vee _ _ = False ve :: Bool - Bool - Bool ve True True = True ve True False = True ve False True = True ve False False = False v :: Bool - Bool - Bool v

Re: [Haskell-cafe] Redefining Disjunction

2007-06-13 Thread Chris Mears
PR Stanley [EMAIL PROTECTED] writes: Hi Can you think of a fourth way of redefining disjunct using pattern matching? vee :: Bool - Bool - Bool vee _ True = True vee True _ = True vee _ _ = False In the same spirit: f False False = False f _ _ = True

RE: [Haskell-cafe] Redefining Disjunction

2007-06-13 Thread Bayley, Alistair
[mailto:[EMAIL PROTECTED] On Behalf Of PR Stanley Hi Can you think of a fourth way of redefining disjunct using pattern matching? vee :: Bool - Bool - Bool vee _ True = True vee True _ = True vee _ _ = False How many ways do you want? I think this is correct, and is only strict in the

Re: [Haskell-cafe] Redefining Disjunction

2007-06-13 Thread Ilya Tsindlekht
On Wed, Jun 13, 2007 at 02:37:37PM +0100, PR Stanley wrote: Hi Can you think of a fourth way of redefining disjunct using pattern matching? vee :: Bool - Bool - Bool vee _ True = True vee True _ = True vee _ _ = False ve :: Bool - Bool - Bool ve True True = True ve True False = True ve

[Haskell-cafe] Re: Construct all possible trees

2007-06-13 Thread apfelmus
Mirko Rahn wrote: apfelmus wrote: data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving (Show) permTrees xs = concat . takeWhile (not . null) . map (flip evalStateT xs . Traversable.sequence) $ trees select where select = StateT $ \xs -

[Haskell-cafe] Reading open data types

2007-06-13 Thread Benja Fallenstein
Hi all, We've had a discussion on #haskell about how we can make a function that reads in serialized values of an open data type, such as class (Show a, Read a) = MyClass a where typeTag :: a - String ... operations on the open data type... data Obj = forall a. MyClass a = Obj { unObj ::

Re: [Haskell-cafe] Reading open data types

2007-06-13 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 Benja Fallenstein wrote: Hi all, We've had a discussion on #haskell about how we can make a function that reads in serialized values of an open data type, such as [...] However, this is still kind of boring. Is there a better way? If not,

Re: [Haskell-cafe] Re: [Haskell] Who pays for *.haskell.org machines?

2007-06-13 Thread brad clawsie
is its funding will be reliable? for example, if we don't get money from Google in 2008 year? in irc some time ago i brought up the topic of something like the freebsd or wikimedia foundations, but for haskell. if you can give me a secure and trustworthy method of payment, and as a bonus, a tax

Re: [Haskell-cafe] Reading open data types

2007-06-13 Thread Benja Fallenstein
Hi Isaac, 2007/6/13, Isaac Dupree [EMAIL PROTECTED]: Since Show instances can overlap (e.g. (show (1::Int)) == (show (1::Integer))), we need to tag with the type. Indeed. But that's the easy part :-) Reminds me of Typeable. Since GHC lets us derive Typeable with a guarantee of different

Re: [Haskell-cafe] Re: [Haskell] Who pays for *.haskell.org machines?

2007-06-13 Thread Bryan Burgers
is its funding will be reliable? for example, if we don't get money from Google in 2008 year? in irc some time ago i brought up the topic of something like the freebsd or wikimedia foundations, but for haskell. if you can give me a secure and trustworthy method of payment, and as a bonus, a

Re: [Haskell-cafe] Re: [Haskell] Who pays for *.haskell.org machines?

2007-06-13 Thread Greg Fitzgerald
is its funding will be reliable? for example, if we don't get money from Google in 2008 year? Some hosting companies, like http://turtol.com/ offer pay once, keep forever. Would that be an option? Thanks, Greg ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Re: [Haskell] Who pays for *.haskell.org machines?

2007-06-13 Thread Bryan O'Sullivan
Bryan Burgers wrote: Similarly, the Perl community has a foundation, and I believe giving to it is tax-deductible. You could look in to how they do it. Setting up a 501(c)(3) foundation is a morass of paperwork. If people within the US are interested in writing tax deductible cheques, a far

Re: [Haskell-cafe] Reading open data types

2007-06-13 Thread Bulat Ziganshin
Hello Benja, Wednesday, June 13, 2007, 6:12:25 PM, you wrote: We've had a discussion on #haskell about how we can make a function that reads in serialized values of an open data type, such as look at Data.Generics.Text which may be implements exactly what you need -- Best regards, Bulat

Re: [Haskell-cafe] Reading open data types

2007-06-13 Thread Benja Fallenstein
Hi Bulat, 2007/6/13, Bulat Ziganshin [EMAIL PROTECTED]: We've had a discussion on #haskell about how we can make a function that reads in serialized values of an open data type, such as look at Data.Generics.Text which may be implements exactly what you need Unfortunately not.

Re: [Haskell-cafe] Re: Construct all possible trees

2007-06-13 Thread Andrew Coppin
Jon Fairbairn wrote: I'm trying to construct a function all_trees :: [Int] - [Tree] such that all_trees [1,2,3] will yield [ Leaf 1, Leaf 2, Leaf 3, Branch (Leaf 1) (Leaf 2), Branch (Leaf 1) (Leaf 3), Branch (Leaf 2) (Leaf 1), Branch (Leaf 2) (Leaf 3), Branch (Leaf 3) (Leaf 1), Branch (Leaf

Re: [Haskell-cafe] Construct all possible trees

2007-06-13 Thread Andrew Coppin
Colin DeVilbiss wrote: On 6/12/07, Andrew Coppin [EMAIL PROTECTED] wrote: Based on the sample output, I'm guessing that the desired output is every tree which, when flattened, gives a permutation of a non-empty subset of the supplied list. This limits the output to trees with up to n leaves.

Re: [Haskell-cafe] found monad in a comic

2007-06-13 Thread Andrew Coppin
Paul Johnson wrote: Marc A. Ziegert wrote: http://xkcd.com/c248.html ( join /= coreturn ) IMHO this could be a beautiful and easy way to explain monads. comments? I read it as a take on Godel Escher Bach, especially the stuff about counterfactual situations. But you are right. Actually

[Haskell-cafe] ghc-pkg list says a package is installed, but ghci won't load its exposed module (HDBC-ODBC)

2007-06-13 Thread Thomas Hartman
ghc-pkg list says a package is installed, but ghci won't load its module (HDBC-ODBC) Any advice? [EMAIL PROTECTED] ~/haskellInstalls/HDBC-odbc-1.0.1.0 $ ghc-pkg list c:/ghc/ghc-6.6.1\package.conf: Cabal-1.1.6.2, GLUT-2.1.1, HAppS-0.8.4, HDBC-1.0.1, HDBC-odbc-1.0.1.0, HUnit-1.1.1,

Re: [Haskell-cafe] Construct all possible trees

2007-06-13 Thread Lennart Augustsson
This doesn't enumerate them in the order you want, but maybe it doesn't matter. module Trees where combinations :: [a] - [[a]] combinations [] = [[]] combinations (x:xs) = combinations xs ++ [ x:xs' | xs' - combinations xs ] data Tree = Leaf Int | Branch Tree Tree deriving (Show) trees

[Haskell-cafe] Re: Construct all possible trees

2007-06-13 Thread Jon Fairbairn
Andrew Coppin [EMAIL PROTECTED] writes: Jon Fairbairn wrote: I'm trying to construct a function all_trees :: [Int] - [Tree] such that all_trees [1,2,3] will yield [ Leaf 1, Leaf 2, Leaf 3, Branch (Leaf 1) (Leaf 2), Branch (Leaf 1) (Leaf 3), Branch (Leaf 2) (Leaf 1),

Re: [Haskell-cafe] Reading open data types

2007-06-13 Thread Stefan O'Rear
On Wed, Jun 13, 2007 at 05:12:25PM +0300, Benja Fallenstein wrote: However, this is still kind of boring. Is there a better way? If not, would it be a good idea to have compiler support for building this kind of type table? The compiler does build exactly such a table - it's called a symbol

Re: [Haskell-cafe] Reading open data types

2007-06-13 Thread Benja Fallenstein
2007/6/14, Stefan O'Rear [EMAIL PROTECTED]: On Wed, Jun 13, 2007 at 05:12:25PM +0300, Benja Fallenstein wrote: However, this is still kind of boring. Is there a better way? If not, would it be a good idea to have compiler support for building this kind of type table? The compiler does build

[Haskell-cafe] Happy, GLR and GHC 6.6

2007-06-13 Thread Iván Pérez Domínguez
Hi everyone, As we all know, FiniteMap was deprecated, and with GHC-6.6 Data.Map must be used instead. Some function names in Data.Map clash with names in prelude, and Map is usually imported qualified. Happy generates GLR parsers (-l), but the templates it uses keep calling FiniteMap

Re: [Haskell-cafe] Happy, GLR and GHC 6.6

2007-06-13 Thread Stefan O'Rear
On Thu, Jun 14, 2007 at 12:38:27AM +0200, Iván Pérez Domínguez wrote: Hi everyone, As we all know, FiniteMap was deprecated, and with GHC-6.6 Data.Map must be used instead. Some function names in Data.Map clash with names in prelude, and Map is usually imported qualified. Happy

Re: [Haskell-cafe] found monad in a comic

2007-06-13 Thread Dan Piponi
Marc asked: http://xkcd.com/c248.html ( join /= coreturn ) IMHO this could be a beautiful and easy way to explain monads. comments? I'll eat my hat if there isn't a formal way of looking at this. I'm not qualified to put it together coherently but it goes something like this: modal logic has

Re: [Haskell-cafe] How to devide matrix into small blocks

2007-06-13 Thread L.Guo
Hi, Henning Thielemann. Thanks for your help. That is usful. I have wrote the target function like this, and tested. mkBlocks (w,h) = map concat . concat . transpose . chop h . map (chop w) Hi, Dr. Janis Voigtlaender. This is not a homework, though likely to be one. I just use Haskell to

[Haskell-cafe] TorDNSEL

2007-06-13 Thread Tim Newsham
I wanted to point out: http://exitlist.torproject.org/ written in Haskell. I haven't seen any announcements or info on this list (apologies if someone else mentioned it already). For the record, I'm not affiliated with the project in any way. Tim Newsham

Re: [Haskell-cafe] TorDNSEL

2007-06-13 Thread Donald Bruce Stewart
newsham: I wanted to point out: http://exitlist.torproject.org/ written in Haskell. I haven't seen any announcements or info on this list (apologies if someone else mentioned it already). For the record, I'm not affiliated with the project in any way. Is the source available? --

Re: [Haskell-cafe] TorDNSEL

2007-06-13 Thread Tim Newsham
I wanted to point out: http://exitlist.torproject.org/ Is the source available? Yup. It's all there on the page: You can download the current revision from the hidden service or from a local mirror. It's probably wise to check out the current version from the darcs repository