[Haskell-cafe] Beginner SOS

2009-05-27 Thread Manu Gupta
Dear anyone,I wish to learn HASKELL. However my institution does not teach
it so plus I don't have a clue how to get around with it. Everything seems
so unconventional and out of place

Can you help me out in getting good tutorials that will help me to learn
HASKELL by myself so that I can pursue it as a serious programming languages

Till now I have referred Haskell wiki and have tried everywhere but does not
seem to learn it

PLZ, PLZ HELP ME OUT

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


[Haskell-cafe] Problem building hdbc-sqlite3 with ghc 6.8.2

2008-01-02 Thread manu

hello,

has anybody managed to build hdbc-sqlite3 with ghc 6.8.2 ?

I get the following error :

Macintosh:HDBC-sqlite3-1.1.3.0 manu$ runhaskell Setup.lhs build
Preprocessing library HDBC-sqlite3-1.1.3.0...
ghc-6.8.2: unrecognised flags: -F/Users/manu/Library/Frameworks
Usage: For basic information, try the `--help' option.
compiling dist/build/Database/HDBC/Sqlite3/Statement_hsc_make.c failed
command was: /usr/local/bin/ghc -c -package base-3.0.1.0 -package  
mtl-1.1.0.0 -package HDBC-1.1.3 -I. -F/Users/manu/Library/Frameworks  
dist/build/Database/HDBC/Sqlite3/Statement_hsc_make.c -o dist/build/ 
Database/HDBC/Sqlite3/Statement_hsc_make.o



if somebody has an idea...

Thanks

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


Re: [Haskell-cafe] Haskell and DB : giving up

2007-11-29 Thread manu


On Nov 29, 2007, at 10:49 AM, Ketil Malde wrote:

I think this is the problem, not the solution.  There is a lot of DB
libraries, just like there are a multitude of XML libraries, several
collections, etc.  Too many libraries are written as research projects
or by grad students, and left to rot after release.  The fragmentation
also means that few libraries see any extensive testing - I was a bit
surprised that apparently none of the XML libraries can handle files
larger than a few megabytes, for instance.



Hello

My post wasn't intended as raging criticism, I can guess that  
developping these libraries takes a lot of (unpaid) work.
And I am grateful for these libraries no matter what. However, if  
what is needed to install and use MySQL (or another popular DB) from  
Haskell could be drastically made shorter and easier, more people  
might use Haskell in domains where it still is largely marginal (like  
say... websites).


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


[Haskell-cafe] Pb building HDBC-sqlite3

2007-11-28 Thread manu

Hello

still, trying to use a database with ghc 6.8.1 - patience running low  
however :)


I now have troubles installing HDBC-sqlite3

the build fails like so :


$ runhaskell Setup.lhs build

Preprocessing library HDBC-sqlite3-1.1.3.0...

Utils.hsc:31:33:
 error: hdbc-sqlite3-helper.h: No such file or directory
Utils.hsc: In function ‘main’:

Utils.hsc:70:0:  error: parse error before ‘finalizeonce’
compiling dist/build/Database/HDBC/Sqlite3/Utils_hsc_make.c failed
command was: /usr/local/bin/ghc -c -package base-3.0.0.0 -package  
mtl-1.1.0.0 -package HDBC-1.1.3 -I. dist/build/Database/HDBC/Sqlite3/ 
Utils_hsc_make.c -o dist/build/Database/HDBC/Sqlite3/Utils_hsc_make.o




the hdbc-sqlite3-helper.h file is nowhere to be found on my system  
should it be part of the package ?


Thanks

M

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


[Haskell-cafe] Pb builind hdbc-sqlite3 (suite)

2007-11-28 Thread manu

Hello,

Still trying to build hdbc-sqlite3

it appears that the hdbc-sqlite3 package on Hackage is missing the C  
header file
It is included with the hdbc-sqlite3 package found at http:// 
software.complete.org/hdbc-sqlite3/downloads however.



Now I have another pb :



Building HDBC-sqlite3-1.1.3.0...
[3 of 7] Compiling Database.HDBC.Sqlite3.Utils ( dist/build/Database/ 
HDBC/Sqlite3/Utils.hs, dist/build/Database/HDBC/Sqlite3/Utils.o )


Database/HDBC/Sqlite3/Utils.hsc:74:8: parse error on input `import'
manu:/Volumes/data/Downloads/HDBC/hdbc-sqlite3 manu$




line 74 is : foreign import ccall unsafe sqlite3.h sqlite3_errmsg

I've checked and I have a sqlite3.h file in /usr/include

what is this parse error on input `import' about ???


Thanks


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


[Haskell-cafe] Pb builind hdbc-sqlite3 (the end)

2007-11-28 Thread manu

Hello

I should think a bit before posting to the list, sorry for the  
pollution !


this error :
Database/HDBC/Sqlite3/Utils.hsc:74:8: parse error on input `import'
manu:/Volumes/data/Downloads/HDBC/hdbc-sqlite3 manu$

can be avoided by adding  ForeignFunctionInterface to the extensions  
in the .cabal file


I also had to add EmptyDataDecls to the extensions

and since adding PatternSignatures cause a parse error (see http:// 
hackage.haskell.org/trac/hackage/attachment/ticket/160/cabal-1.2.0- 
extensions.patch)


I added this pragma {-# LANGUAGE PatternSignatures #-}
at the top of Statement.hsc and Connection.hs

It did build ! Victory !

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


[Haskell-cafe] Haskell and DB : giving up

2007-11-28 Thread manu

Hello

I've spent a few days trying to install all the packages required to  
use HaskellDB with either MySQL or SQlite3

(the only 2 DB the host I was thinking about is supporting)

Well, I am giving up ! I seriously regret replacing ghc-6.6 with  
ghc-6.8, I didn't expect that building packages would be so ...

unsucessfull and time-wasting.

I just thought I'd let you know what's in store for PHP-style-users- 
like-me who want to use a database with ghc-6.8.1 at the moment, the  
hurdle is high !


I hope these packages will be fixed soon (I can't figure how to fix  
them myself obviously).


And now I'm going to stay away from my computer for a while :)

cheerio

M




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


[Haskell-cafe] Re: Haskell-Cafe Digest, Vol 51, Issue 180

2007-11-28 Thread manu


I'm trying to build diverse packages from Hackage with ghc 6.8.1,
they usually fail to build because of missing language extensions.

Sometimes I am unable to determine the proper name of the extension
missing in .cabal
I tend to slap {- #OPTIONS -fglasgow-exts #-} at the top of the
troublesome file.
It works, but out of curiosity, what is the downside of such an
approach ? (bigger executables ?)


Can you list which packages failed to build out of the box?

 -- Don




Well I'd say none of the packages I've tried, build out of the box,  
that include :


haskelldb
haskelldb-hdbc
haskelldb-hdbc-sqlite3
HDBC
HDBC-sqlite3

Agreed some of these compile right after tweeking the build-depends:  
and extensions: lines in the .cabal file
(apart from the pesky PatternSignatures which require a LANGUAGE  
pragma in the source file)


haskelldb-hdbc-sqlite3 is the one that I couldn't get past...

I didn't bother with hsql-mysql-1.7 since Duncan Coutts mentioned it  
required significant work (and I cannot do much)


Manu


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


[Haskell-cafe] Cabal and DB packages

2007-11-25 Thread manu

Hello,

I'm trying to do something that should be fairly simple, installing  
some DB package so I can use MySQL or SQLite.


However I've had troubles building HSQL, HaskellDB and Takusen before  
giving up (I am using ghc 6.8.1 and Cabal-1.2.2.0).


--

with HSQL :

Database/HSQL.hsc:66:7:
Could not find module `System.Time':
  it is a member of package old-time-1.0.0.0, which is hidden

so I added 'old-time' to the 'build-depends' line in the .cabal file

but then it fails building with

Building hsql-1.7...
[1 of 2] Compiling Database.HSQL.Types ( Database/HSQL/Types.hs, dist/ 
build/Database/HSQL/Types.o )


Database/HSQL/Types.hs:134:18: Not in scope: type variable `forall'

Database/HSQL/Types.hs:134:25: Not in scope: type variable `a'

Database/HSQL/Types.hs:134:27:
Illegal operator `.' in type `forall a . (Int
  - FieldDef
 - (FieldDef -  
CString - Int - IO a) - IO a)'

  (Use -XTypeOperators to allow operators in types)

etc...

At this point, it goes over my head...

---

What the hell, I'll use HaskellDB and FlatDB, but then I get this  
message while building HaskellDB :


src/Database/HaskellDB/HDBRec.hs:106:11:
Illegal signature in pattern: l f a
Use -XPatternSignatures to permit it

when I add 'PatternSignatures' to the 'Extensions:' line in .cabal,  
it fails configuring with :


Setup.hs: haskelldb.cabal:8: Parse of field 'extensions' failed:

Jsus, nevermind, I'll try Takusen

---

with Takusen :

$ runhaskell Setup.hs configure

Setup.hs:26:7:
Could not find module `Distribution.Program':
  Use -v to see a list of the files searched for.

I give up...



Is there any simple way to do it though ? Is there any problems with  
Cabal that I need to work around ?


Help !!

Manu


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


[Haskell-cafe] WideFinder

2007-11-07 Thread manu
Haskell is conspicuously absent from the languages used to tackle Tim  
Bray's Wide Finder problem (http://www.tbray.org/ongoing/When/200x/ 
2007/10/30/WF-Results?updated).

So far we have Ocaml, Erlang, Python, Ruby, etc...

Bryan quickly wrote a program on his blog (http://www.serpentine.com/ 
blog/2007/09/25/what-the-heck-is-a-wide-finder-anyway/) that would  
place Haskell right in the second position.


JoCaml is the fastest so far (http://eigenclass.org/hiki.rb?fast- 
widefinder)...


Can Haskell do better ? Care to take a shot ?


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


Re: [Haskell-cafe] Why can't Haskell be faster?

2007-10-31 Thread manu

From what I've seen of Clean it seems almost like Haskell. It even


distributes a Haskell-Clean translator so the obvious question is,
why is Haskell slower?



It's also something I've wondered about, and I'm curious about the  
answer...


One of the differences between Haskell and Clean is how side-effects  
are allowed

(Uniqueness Types for Clean, and Monadic I/O for Haskell)

GHC also supports a lot of extensions beyong Haskell98.

Does it explain the difference in performances ? I don't know...

Experts please !


Manu


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


[Haskell-cafe] What algorithm to use ?

2007-10-22 Thread manu

Hello

I am not sure it is appropriate to post to this mailing list to  
inquire about a peculiar algorithm, if not let me know...


I was looking at one particular puzzle posted on the Facebook site,  
'Wiretaps' (http://www.facebook.com/jobs_puzzles/?puzzle_id=11).  
Briefly, you have 26 programmers (numbers 1 to 26) which need to be  
assigned a job (a name to decode).
Even numbered programmers spend 1.5 hours more per vowel. Odd ones  
spend 1 hour more per consonant. And finally, each programmer whose  
number share primes factors with the length of the name to decode,  
spend 2 hours extra per factor (For example, it takes programmer 12  
-- factors of 2 and 3 -- an extra 4 hours to decode 'NORMAN')


The point is to come up with the combination of (programmer, name)  
which minimizes the time taken overall.


Now the simplest solution, conceptually, is calculating the time  
taken by each combination, and pick the fastest...
However looking at the number of permutations (26! =  
40329146112660563558400), quickly dampened my enthusiasm...


There must be some algorithm (dynamic programming ?), that cuts down  
the number of calculations involved in order to find the right  
combination. But I cannot identify the proper algorithm to use...


Can someone give me a tip ? Can some of the computations be  
parallelized ?


(it's not an assignment, nor will I send anything to Facebook, I am  
just trying this out of curiosity)


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


Re: [Haskell-cafe] Suspected stupid Haskell Question

2007-10-17 Thread manu

 The problem there is that nub is O(n^2).

Is there a place where one can look up the complexity of Standard  
Libraries functions  ?



E.D
 
___

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


[Haskell-cafe] Re: Tiny documentation request

2007-09-12 Thread manu


On Sep 11, 2007, at 9:58 PM, Miguel Mitrofanov wrote:



Well, I'm not a web designer, but I did work with few of them, and it
seems to me that you either create a table design in two hours or
spend three days trying to create a CSS one and THEN create a table
design in two hours.


That's an exaggeration.
It's widely accepted than tables can straightforwardly be dropped in  
most cases.

They are intented to be used to present tabular datas, NOT for layout.
(This ideas is not new, Zeldman talked about it in 2001)
It does require a bit of CSS-Fu, however, as  CSS support in browsers  
varies...

But hey, you've got to occupy these HTML-CSS guys !

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


[Haskell-cafe] Re: Tiny documentation request

2007-09-11 Thread manu


On Sep 11, 2007, Simon Marlow wrote:


Please, please, someone do this for me.  I tried, and failed, to  
get the
layout right for the contents list in all browsers at the same  
time.  The

semantics of CSS is beyond my comprehension.

Cheers,
Simon


Hi Simon,

On the page http://www.haskell.org/ghc/docs/latest/html/libraries/ 
index.html, you only need tables to display the foldable lists of  
modules (HTML tables were commonly used to display many things on a  
same line), but they can be replaced by nested lists with a bit of CSS :


Check this page out : http://la.di.da.free.fr/haddock/

I can help further, if need be.

Emmanuel


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


Re: [Haskell-cafe] Tiny documentation request

2007-09-10 Thread manu

Neil Mitchell wrotes :

Replicating actual tables with CSS is a nightmare - you shouldn't use
table's for lots of things,


I agree


but there are sometimes when it really is
the best option.


Which isn't the case here !
Nested lists would easily do the trick...


Fixing up the CSS and still keeping tables is a
perfectly valid option.


yes it's true...


E.D




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


Re: [Haskell-cafe] Norvig's Sudoku Solver in Haskell

2007-08-27 Thread manu
Daniel Fischer's modifications to my original program lead to a 400 %  
speed boost !!!

(It now runs in 22 seconds on my machine)
He avoided unecessary calls to 'length', uses Array instead of Map,  
refactored 'search' function (details below)


I've put up his version on hpaste : http://hpaste.org/2452#a1

Manu



On Aug 26, 2007, at 10:56 PM, Daniel Fischer wrote:

Without much thinking I can spped it up by a factor of 4 (from 280s  
to 60s).

The most important things are:
- don't use length unless you need it
instead of
newV2 - case length newCell of
0 - Nothing
...
and
case length dPlaces of
0 - ...
use
case newCell of
[] - Nothing
[d'] - ...
and
case dPlaces of
[] - Nothing
[s'] - ...

- let dPlaces = [ s' | u - lookup s units, s' - u, elem d (lookup  
s' newV2)]

is bad
let dPlaces = [s' | s' - lookup s peers, elem d (lookup s' newV2)]
scans each peer only once

- search is really bad, you lookup all squares several times,  
potentially

compute all lengths multiple times...
much better is

search :: Grid - Maybe Grid
search g = case [(l,a) | a@(_,xs) - M.assocs g, let l = length xs,  
l /= 1] of

[] - return g
ls - do let (_,(s,ds)) = minimum ls
 msum [assign g (s,d) = search | d - ds]

(I also changed the type, and instead of foldl' you should use  
foldr, since
some is lazy in the second argument, further, since Maybe is a  
MonadPlus,

it's mplus and 'foldr mplus Nothing' is msum)

- Maps aren't good here, too slow lookup and you know the keys, so  
use arrays




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


Re: [Haskell-cafe] Norvig's Sudoku Solver in Haskell

2007-08-27 Thread manu

From: Daniel Fischer
 Thought it was something like that.
 Must check whether that beats Norvig's constraint propagation.

it does !

on my machine :

Jon Harrop's : 12.5 sec  and Norvig's : 15 sec


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


[Haskell-cafe] Norvig's Sudoku Solver in Haskell

2007-08-26 Thread manu

Hello,

After reading Peter Norvig's take on writing a Sudoku solver (http:// 
norvig.com/sudoku.html)
I decided that I would port his program to Haskell, without changing  
the algorithm, that'll make a nice exercise I thought

and should be fairly easy... Boy, was I wrong !

Anyway, I eventually managed to tiptoe around for loops, mutable  
state, etc...
However, when I run my program against the test data provided (http:// 
norvig.com/top95.txt),
I find it takes around 1m20 s to complete (compiled with -fvia-C and - 
O2, on a MacBook Pro 2.33GHz Intel Core 2 Duo).
That's roughly 8 times longer than Norvig's Python script. That's not  
what I expected !

My program is also longer than the Python version.

Being a beginner, I am convinced my implementation is super naive and  
non idiomatic. A seasonned Haskeller would do much shorter and much  
faster. I don't know how to improve it though !


Should I introduce more strictness ? replace lists with more  
efficient data structures (ByteStrings, Arrays) ?


Here is my program, and part of the profiling (memory allocation  
looks huge !)


I hope this post wasn't too long. Thanks for any advice !

Emmanuel.

{-

This is an attempt to implement in Haskell, Peter Norvig's sudoku  
solver :

Solving Every Sudoku Puzzle (http://norvig.com/sudoku.html)

In Norvig's program, methods which change a grid return either a new  
grid, either False (failure).

Here I use Maybe, and return Just grid or Nothing in case of failure

-}

module Main where

import Prelude hiding (lookup)
import Data.List hiding (lookup)
import qualified Data.Map as M
import Control.Monad
import Maybe
import System.IO

--
-- Types
type Digit  = Char
type Square = String
type Unit   = [Square]

-- We represent our grid as a Map
type Grid = M.Map Square [Digit]


--
-- Setting Up the Problem

rows = ABCDEFGHI
cols = 123456789
digits = 123456789

cross :: String - String - [String]
cross rows cols = [ r:c:[] | r - rows, c - cols ]

squares :: [Square]
squares = cross rows cols  -- [A1,A2,A3,...]

unitlist :: [Unit]
unitlist = [ cross rows [c] | c - cols ] ++
   [ cross [r] cols | r - rows ] ++
   [ cross rs cs | rs - [ABC,DEF,GHI], cs -  
[123,456,789]]


units :: M.Map Square [Unit]
units = M.fromList [ (s, [ u | u - unitlist, elem s u ]) | s -  
squares ]


peers :: M.Map Square [Square]
peers = M.fromList [ (s, set [[ p | p - e, p /= s ] | e - lookup s  
units ]) | s - squares ]

  where set = nub . concat

--
-- Wrapper around M.lookup used in list comprehensions

lookup :: (Ord a, Show a) = a - M.Map a b - b
lookup k v = case M.lookup k v of
Just x - x
Nothing - error $ Error : key  ++ show k ++  not  
in map !


-- lookup k m = fromJust . M.lookup k m
--
-- Parsing a grid into a Map

parsegrid :: String - Maybe Grid
parsegrid g= do regularGrid g
foldM assign allPossibilities (zip squares g)

  where  allPossibilities :: Grid
 allPossibilities = M.fromList [ (s,digits) | s - squares ]
 regularGrid   :: String - Maybe String
 regularGrid g  = if all (\c - (elem c 0.-123456789)) g
 then (Just g)
 else Nothing

--
-- Propagating Constraints

assign:: Grid - (Square, Digit) - Maybe Grid
assign g (s,d) = if (elem d digits) then do -- check that we are  
assigning a digit and not a '.'

let toDump = delete d (lookup s g)
res - foldM eliminate g (zip (repeat s) toDump)
return res
 else return g

eliminate ::  Grid - (Square, Digit) - Maybe Grid
eliminate g (s,d) = let cell = lookup s g in
if not (elem d cell) then return g -- already  
eliminated

-- else d is deleted from s' values
   else do let newCell = delete d cell
   newV = M.insert s newCell g --
   newV2 - case length newCell of
   -- contradiction :  
Nothing terminates the computation

   0 - Nothing
   -- if there is only one  
value (d2) left in square, remove it from peers
   1 - do let peersOfS =  
[ s' | s' - lookup s peers ]
   res - foldM  
eliminate newV (zip peersOfS (cycle newCell))

   return res
   -- else : return the new  
grid

   _ - return newV
   -- Now check 

Re: [Haskell-cafe] Norvig's Sudoku Solver in Haskell

2007-08-26 Thread manu

From: Malte Milatz [EMAIL PROTECTED]
Subject: Re: [Haskell-cafe] Norvig's Sudoku Solver in Haskell

Your program was wrapped by your mail client, so you may want to  
hpaste

your program for easier digestion.



here it is : http://hpaste.org/2452



Your profiling output suggests that much time is consumed by the  
lookup

function. Since you're using (fromJust . lookup) everywhere anyway, a
data structure not envolving the Maybe type is probably a more succint
choice. And why bother with characters and strings?



no rationale except that's what the original Python script did use





 newV2 - case length newCell of
 0 - Nothing
 1 - do let peersOfS =  [ s' | s' - lookup s peers ]
 res - foldM  eliminate newV (zip peersOfS  
(cycle newCell))

 return res
  _ - return newV


The use of “length” here is not an actual performance problem, but
unnecessary. Simply write: case newCell of []  - ...
  [_] - ...
  _   - ...

The same is valid for your other use of length.

Malte


I see, thanks !

E.D





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


[Haskell-cafe] Building c2hs on a mac

2007-04-06 Thread manu

Hello,

I'd be interested to know if anybody had managed to build c2hs on a  
mac recently
because I've tried the current darcs version, c2hs-0.14.5,  
c2hs-0.14.3, c2hs-0.13.6, etc...

to no avail

I get this with c2hs-0.14.5 :

./Setup.hs configure

./Setup.hs:11:57:
Couldn't match expected type  
`Distribution.PackageDescription.PackageDescription'

   against inferred type `LocalBuildInfo'
Probable cause: `addWrapperAndLib' is applied to too many arguments
In the `postInst' field of a record
In the first argument of `defaultMainWithHooks', namely
`defaultUserHooks {postInst = addWrapperAndLib}'


Any help appreciated, thanks

E.D

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