[Haskell-cafe] ANNOUNCE: graphtype — A simple tool to illustrate dependencies between Haskell types

2009-08-24 Thread Max Desyatov

While developing applications which deal with complex data it is crucial
to know how exactly you manipulate this data.  Haskell provides excellent
tools for expressing a data scheme you work with: ADTs, `type` and `newtype`
declarations, type classes and much more is hidden in rich Haskell's
type system.  Obviously, when types of data in your domain you work with
grow — all declarations grow, and it becomes hard to grasp all
dependencies, to change them and to remove them deliberately.

graphtype was developed to visualise type declarations in you Haskell
source files.  It produces .dot-file for subsequent processing with
graphviz.

Results for example file bundled with graphtype:
http://i.piccy.info/i4/00/90/bfa07290012c2d3b455696bdaa86.png

To play with it, you can use hackage: 
http://hackage.haskell.org/package/graphtype
or hack some code: http://github.com/explicitcall/graphtype

Visualisation of dependencies in complex type class hierarchies is still
on the way.  It isn't obvious how do to this nicely, as in most cases
type class declarations are imported from other libraries, and you don't
always have source files for them.

Anyway, graphtype is fairly usable.  Leave here your questions,
suggestions and have fun looking at type dependencies in your code.

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


[Haskell-cafe] Generics for constructing Rows

2009-08-20 Thread Max Desyatov

Hi, all.

I've come into trouble defining function `gmap` which will work on these
data types:

 data Row = Row
  (E Name)
  (E Salary)
  (E Department)

 type E a = Either (Maybe RowIndex) (Maybe a)

 type RowIndex = Int

`RowIndex`, `Name`, `Salary`, `Department` have kind *

pseudocode:

 gmap :: (E a - E a) - Row - Row

 readRow :: [String] - Row - Row
 readRow l = gmap (\(Left (Just ri)) - Right $ l `atMay` c = readMay)

`atMay` and `readMay` are defined in module `Safe` from package `safe`

 atMay :: [a] - Int - Maybe a
 readMay :: (Read a) = String - Maybe a

Basically we have optional Row indices and try to read raw row (list of
Strings) into the same Row type if index is present.  At this moment I
just have separate data type for row which has been read and just a list
of row indices, but it is definitely flawed when I need to add fields to
Row from time to time, as it is too easy to introduce bugs while
positioning in list of row indices, not mentioning all those boilerplate
code flowing around.

I've tried to define gmap using libraries for generic programming but
failed each time while type checking for different reasons.  With
`Data.Generics` and `gmapT` it fails because gmapT doesn't allow
traversion function to have `Read a` constraint (Data and Typeable
instances for Row and inner data types of course were derived).  EMGM's
map demands traversion function to be non-polymorphic, i.e. type-checker
fails with the message, complaining it cannot match `E a` against
`E Name`, against `E Salary` etc.  For each of this I've spent smth about
five hours just reading API docs, papers, and trying to beat
type-checker.  Maybe I'll look into Smash, RepLib and others, but I hope
someone was also trying to define such gmap and succeeded.

So, generic programming folks, is it even possible to define such
function?  I don't really care about using GHC extensions, I don't care
about code being portable, I just want to remove boilerplate and prevent
introducing bugs.

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


[Haskell-cafe] Generics for constructing Rows

2009-08-20 Thread Max Desyatov

Sorry for a type and probably confusing you, it must be:

 readRow l = gmap (\(Left (Just ri)) - Right $ l `atMay` ri = readMay)

instead of

 l `atMay` c

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


Re: [Haskell-cafe] Where does documentation get installed with cabal?

2009-08-20 Thread Max Desyatov
Colin Paul Adams co...@colina.demon.co.uk writes:

 I'm trying to find the API documentation for happstack 0.3 (online is
 for 0.2).

 So I did:

 cabal install happstack --reinstall --enable-documentation

 but I can't find it anywhere within ~/.cabal - where should I look?

In most cases it is installed in ~/.cabal/share/doc/happstack*/html.  Is
there any files at that directory?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Generics for constructing Rows

2009-08-20 Thread Max Desyatov
Sean Leather leat...@cs.uu.nl writes:

 I'm not sure the problem you're running into is strictly a generic
 programming (GP) one. Typically, GP takes code that is often written
 and generalizes it, so that it doesn't have to be written for multiple
 datatypes.

That seems to be GP problem, as your solution doesn't scale well when I
wan't to add/remove/change fields in the `Row` record.  The perfect way
as I see it, would be just editing `Row` data declaration, nothing else.
Studying few papers about GP in Haskell, I reckon this could be
represented as generic traversal, using my `Row` declaration with
`Either`.  I don't see really good way to write a generic producer from
`[String]` to version of `Row` without `Either`.  But SYB doesn't
provide a way for passing type-class-parametric functions to gmapT, and
SYB-with-class has large overhead of its usage.  I don't have enough
time to find out how this can be written in SYB-with-class, if it really can be
written.  The restriction of EMGM was described in my initial message.

 For your problem, I think the first issue is figuring out how to write
 the non-generic function. I don't know if this is exactly what you
 want, but you can write a version of gmap using GADTs and rank-2
 types. I've simplified some types, but it should be easily
 transferable to your code. For example, change the String, Float,
 etc. to your Salary, Department, whatever.

 ---

 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE Rank2Types #-}

 module Main where

 data T a where
   String  :: T String
   Float   :: T Float
   Integer :: T Integer

 data Row = Row (Maybe String) (Maybe Float) (Maybe Integer)
   deriving Show

 f :: T a - Maybe a - Maybe a
 f String (Just a) = Just z
 f _  x = x

 gmap :: (forall a . T a - Maybe a - Maybe a) - Row - Row
 gmap f (Row x y z) = Row (f String x) (f Float y) (f Integer z)

 main = do
   print $ gmap f $ Row Nothing (Just 5.4) (Just 3) -- == Row Nothing (Just 
 5.4) (Just 3)
   print $ gmap f $ Row (Just a) Nothing Nothing -- == Row (Just z) 
 Nothing Nothing


 If this is what you're looking for, then I think it might be possible to do 
 this more generally, though I haven't looked
 into it.

Many thanks for this code, I'll try to integrate it at this point.  It
seems to remove the burden of managing row indices list and implements
some intended restrictions that will make my code less error prone, I
hope.

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


Re: [Haskell-cafe] Can't derive Binary for StdGen

2009-08-20 Thread Max Desyatov
Grigory Sarnitskiy sargrig...@ya.ru writes:

 Hello! I'm trying to derive Binary for StdGen with DrIFT:
[...]
 but I got  error  DrIFT: can't find module System/Random
 What shall I do?

I'd use
http://hackage.haskell.org/packages/archive/derive/2.0.1/doc/html/Data-Derive-Binary.html
instead.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Planning for a website

2009-08-18 Thread Max Desyatov
Simon Michael si...@joyful.com writes:

 I can give a +1 vote for the Hack api and related libs. (Jinjing Wang
 is a one-man army.) Below hack you'll run happstack or another
 web-serving lib. Above hack you might run some combination of loli,
 maid, the hack middleware modules, hsp.

 The advantage is that changing the low-level server in future is a
 matter of changing one or two lines; and the upper-level utilities
 seem more usable to me than current happstack's.

The problem is that `hack` isn't documented at all and that prevents it
from being in wide use.  At least, when I started my web app, I
preferred happstack, as low-level and documented API is better than
high-level API without a little bit of documentation, examples and
tutorials.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell-beginners] Ambigous Types with Haskell Functional Graph Library

2009-08-17 Thread Max Desyatov
Joe joesmo...@gmail.com writes:
 I tried using ucycle directly from Data.Graph.Inductive.Example by
 itself.

 I didn't realize there were two instances of Graph.  How would you use the
 PatriciaTree Graph instance in the ucycle type signature?

 ucycle :: Graph gr = Int - gr () ()

You must have that Graph instance in scope.  I can't give any more
suggestions as I don't see the code in which you use `ucycle`.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Changelogs and available since

2009-08-17 Thread Max Desyatov
Laszlo Nagy rizso...@gmail.com writes:

 Hi All,

 I was volunteer to solve this problem:
   http://hackage.haskell.org/trac/summer-of-code/ticket/1565
 In a conversation on the librar...@haskell.org I was suggested to
 scratch my idea here.


 I would use hoogle for this. Currently it stores the package name and
 the symbols of the modules about a package. 

What do you think about hayoo?  I prefer this to hoogle, as hayoo has
more complete database across hackage packages, AFAIK

 I would extend it to store
 the version of the package as well. Extend the query methods to use
 all the available package description at search. And make a
 VersionRange from the matched Versions.

I wrote some code for doing this a while ago.  Take a look and make some
comments, I can extend this library to satisfy your needs

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


Re: [Haskell-cafe] Re: simple hsql question

2009-08-17 Thread Max Desyatov
Alexander Kotelnikov sa...@myxomop.com writes:

 Ok, let me ask it in another way. Is there a good way to access
 databases, mysql in particular, from haskell program?

Use HDBC or Takusen.  You can find them on hackage.  HDBC is fairly usable,
but you must write SQL queries by yourself or use some simple machinery
to construct queries.  I've written a bunch of helper functions to
construct queries as strings, e.g.:

 insert :: String - [String] - String - String
 insert t = (++)  .
   ( INSERT  ++)   .
   ( INTO++)   .
   (t ++).
   ( ( ++) . (++ ) ) .
   join , 

 select :: [String] - String - String
 select = (++) . ( SELECT  ++) . join , 

 from   :: [String] - String - String
 from   = (++) . ( FROM++) . join , 

In the end your query looks like:

 query' (select [max(cheque)] . from [history] $ ;

In this way you avoid typical errors which emerge when you write simple
SQL query strings.  Though you don't get true static typing.

There are haskelldb and Takusen, which provide more elaborate way of
connecting to RDBMS, they demand more investigation though.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] unsafeDestructiveAssign?

2009-08-11 Thread Max Desyatov
Job Vranish jvran...@gmail.com writes:

 Does anybody know if there is some unsafe IO function that would let me do 
 destructive assignment?
 Something like:

 a = 5
 main = do
   veryUnsafeAndYouShouldNeverEveryCallThisFunction_DestructiveAssign a 8
   print a
 8

Aren't StateT or IORefs the exact thing you are looking for?

 I'm also looking for a way to make actual copies of data.
 so I could do something like this:

 a = Node 5 [Node 2 [], Node 5 [a]]
 main = do
   b - makeCopy a
   veryUnsafeAndYouShouldNeverEveryCallThisFunction_DestructiveAssign b (Node 
 0 [])
   -- 'a' is unchanged

 It would be even more fantastic, if the copy function was lazy.
 I think the traverse function might actually make a copy, but I would be 
 happier with something more general (doesn't
 require membership in traversable), and more explicit (was actually designed 
 for making real copies).

Same thing, IORefs could help you.  Anyway, I can't imagine any case
where veryUnsafeAndYouShouldNeverEveryCallThisFunction_DestructiveAssign
could be useful with its imperative semantics as you've described.  The
point is that Haskell is pure language and I use it because of this
feature (not only because of this, to be exact).  I don't want to use
any library code that brokes pure semantics and launches nuclear bombs
behind the IO monad.  GHC is smart enough these days to do all optimised
destructive assignments, copies and all that imperative stuff and there
are plenty of other ways to get a performance boost without
unsafeHorribleThings.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] unsafeDestructiveAssign?

2009-08-11 Thread Max Desyatov
Job Vranish jvran...@gmail.com writes:

 I am well aware of the usual ST/IORefs as the usual solutions to data 
 mutability in haskell.
 I very very much understand purity, and why it is a good thing, and why we 
 should try to stay away from IO and ST as much
 as possible.
 I am very much away that even if I had such a function that it will probably 
 break everything.
 I am not just trying to make things run faster.

 What I am trying to do is hyper unusual and I really do need an 
 unsafeHorribleThings to do it.

Well, is purpose of this a big secret?  Maybe if you describe the whole
direction of such efforts, somebody could propose better solution that
satisfies your needs.

I recommend you to describe semantics of unsafeHorribleThings in
details, and in what exact cases this could be useful.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell's type system compared to CLOS

2009-08-11 Thread Max Desyatov
Matthias-Christian Ott o...@mirix.org writes:

 That's true. This is a big advantage when compiling programmes. But as
 far as I know type inference is not always decidable in Haskell. Am I
 right?

Decidability of type inference depends on features you use (GADTs, type
classes etc).  Type inference in Haskell doesn't mean you avoid
providing type signatures at all costs.  It is good programming practice
to provide type signatures, as elaborate design of ADTs, type classes
you use in your program gives you possibility to encode specification of
how program behaves in static, that is type signatures help you to
document your code.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: cabal-query 0.1

2009-08-09 Thread Max Desyatov

This package was written to assist you at finding a set of packages,
which satisfy your needs. At the moment it doesn't have a standalone
executable, but you can do the queries from your Haskell code.

It uses Data.Generics.PlateData, so

 * when Cabal package format changes, we don't have to rewrite anything
 * all queries are statically typed
 * as a disadvantage, we may suffer some performance loss when doing
   very complex queries, anyway most of processing goes while we read
   package descriptions, not querying them

Example of enduser querying code:

 module Main where

 import qualified Data.ByteString.Lazy as B
 import System.Environment
 import Distribution.Query
 import Distribution.Compiler
 import Distribution.License
 import Distribution.ModuleName hiding (main)
 import Distribution.Package
 import Distribution.PackageDescription
 import Distribution.Version
 import Distribution.Text
 import Language.Haskell.Extension

 main = (head `fmap` getArgs) =
 B.readFile =
 mapM_ (putStrLn . show . (x - (display $ package x, display $ 
 license x))) .
 queryIndex (Not (Id (== GPL)) : Not (Id (== BSD3)))

This queries an index file, which is commonly located at
~/.cabal/packages/hackage.haskell.org/00-index.tar in POSIX systems.

You can query any field of PackageDescription no matter how deep it
is. You don't need to provide any type signature for comparison
functions, which are wrapped in Id, as long as you use data constructors
for which type can be inferred.

In the future versions I want to add some query expressions parser, for
invoking cabal-query from command-line.  I suppose this will look like:

cabal-query -q 'license == BSD3  stability == stable 
testedWith == GHC  repoType == (git | darcs)' 
path_to_cabal-files_or_index-file
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Request for Changelogs

2009-08-06 Thread Max Desyatov
Did you see these tickets
http://hackage.haskell.org/trac/hackage/ticket/299
http://hackage.haskell.org/trac/hackage/ticket/244 ?

Probably the real proposal could be fixed in comments for that tickets,
so anyone who wants to implement that feature would see all possible
solutions in one place, without browsing through haskell-cafe archives.

Joachim Breitner m...@joachim-breitner.de writes:
 If the changelog had a properly specified format and location, cabal
 upgrade could, if the user wants it, tell him all the downloaded
 changes. This really helps him to keep up-to-date. It is also a good
 channel for the authors to talk to his users („see this nice module I
 added to the package“, „some parts of the API are deprecated now, please
 move to this part“). Last but not least having documented changes is QA
 measure that the Haskell platform in the wider sense deserves.

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


Re: [Haskell-cafe] Re: SQL Database in Haskell?

2009-08-05 Thread Max Desyatov
As I can say from my experience of usage of hdbc-sqlite3 and
happstack-state, the latter covers everything you ever wanted from
sqlite3 and more.  It you aren't too concerned about performance, you
can free yourself from many tedious routines that are imminent when you
work with relational database.  Elaborated data model design coupled
with some generics technique (uniplate with derive, e.g.) gives you a
possibility to write down your domain problem directly to haskell.

CK Kashyap ck_kash...@yahoo.com writes:

 I'd be very interested to see a rdbms implementation in Haskell ...
 perhaps a port of sqlite

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


[Haskell-cafe] [GSoC] WWW::Mechanize-like package for Haskell

2008-04-07 Thread Max Desyatov
Hi,

I'm interested in working on a library for a stateful web browsing in
Haskell during Google Summer of  Code.  The basic idea is described at
http://hackage.haskell.org/trac/summer-of-code/ticket/1107.
WWW::Mechanize is a ready to use library written in Perl, though I
used python's mechanize when I wrote some simple scripts
(http://wwwsearch.sourceforge.net/mechanize/), which provides much
cleaner interface.  Anyway, it gives simple and convenient way to
retreive web-sites, to handle cookies, history and to process
retrieved content and forms.  There are basics of it Network.Browser
module from Haskell's HTTP library
 
(http://hackage.haskell.org/packages/archive/HTTP/3001.0.4/doc/html/Network-Browser.html),
but it's ugly (uses unsafePerformIO for error reporting) and lacks a
greater part of needed functionality.

My aim is to greatly improve Network.Browser module and to make coding
small scripts with it in more functional way possible.  At this moment
it uses BrowserAction state monad.  Though, the deadline is
approaching, I still seek some ways to improve my proposal.  So here
are the questions: are there any other data structures that will make
programming with this library more convenient, besides simple state
monad?  Should we contrive more sophisticated system with other other
separate data structures?  What other improvements you'd like to see?

Thanks in advance for any advice.

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


Re: [Haskell-cafe] [GSoC] WWW::Mechanize-like package for Haskell

2008-04-07 Thread Max Desyatov
On Mon, Apr 7, 2008 at 4:11 PM, Thomas Schilling
 [EMAIL PROTECTED] wrote:
   It doesn't have to be perfect.  Make sure you know how to use monad
  transformers.  Also take a look at tag soup and the various HTML/XML
  parsers.  I'm sure there's plenty to work on.
 
   My guess would be, that you try to write non-trivial example applications
  and see what is needed.  For example, you could write a script to
  download/upload a Haskell wiki page logging in if necessary.  Take a look of
  what other WWW::Mechanize packages are used.  That kind of stuff.
 
   Also, for a GSoC proposal you should try to convince the mentors, why your
  project is useful for Haskell in general.  So maybe you have some more
  arguments there, too.
 
   / Thomas

 There's many benefits of having such library in Haskell: improved
 automated testing (as Yitzchak Gale mentioned) due to pure nature of
 inner algorithms (BrowserAction can be pure and be transformed into IO
 only on demand), static typing (just hate a bunch of stupid bugs while
 writing all those scripts in python/perl).  We can use powerful
 HTML/XML parsers available there in Haskell (HXT with its arrowed
 XML filters).

 Haskell community will definitely benefit from such library. Firstly,
 as I see, in indirect way: I know many people that don't want to use
 or learn more about Haskell, saying it lacks libraries for their
 everyday work.  Network libraries still aren't cool enough, and
 personally I want to improve them at least to the point when I can say
 look! here's the network libraries and they aren't worse than yours,
 even better: pure and checked! :).  Secondly, new libraries are
 useful for the community directly, we have aforementioned lambdabot,
 e.g.  I'd like to write some bots looking at new changes at
 haskellwiki or something like that, thing I'm doomed to code in
 shcurl/perl/python now.

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