Re: [Haskell-cafe] Applicative instances for Monads
On 9/24/10 10:01 PM, Gregory Crosswhite wrote: Hey everyone, There is something that has been bugging me recently about the Applicative class and the Monad class. Any type constructor F that is a Monad has a natural Applicative instance, (<$>) :: F (a -> b) -> F a -> F b mf <$> ma = do f <- mf a <- ma return (f a) Er, I'm pretty sure you mean (<*>) not (<$>) :) So it seems that defining something to be a Monad should automatically make it an instance of Applicative with this definition for (<$>). So far so good, but there are times when this implementation is too "sequential". The nature of Applicative is that later actions are not allowed to depend on earlier actions, Yes and no. Later actions are not allowed to depend on the resulting value of earlier actions, but they are most certainly allowed to 'depend' on the side-effects of earlier actions. Otherwise applicative parser combinators wouldn't make any sense because there's be no way to sequence their effects of consuming input. It would be nice to have something like AIO in a standard library though. -- Live well, ~wren ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Inverse of HaskellDB
>Have you given any thought as to how you want to approach versioning? After giving this some more thought, I realized: 1) One of the "best practices" (even though I despise the term) of versioning schema is to include a script with the code which checks for each change to the tables, and makes the change if it is needed [1]. Each time you check out new code, you run the script to ensure that the code you are working with matches the tables you are working with. 2) A system that generates tables from Haskell types could also be made to check if a given table faithfully represents a given Haskell record type. It could then make any changes to the table so that it _does_ faithfully represent the record type. 3) In this way, your Haskell records ARE your table update script, just (like most Haskell code) incredibly terse. Your usual code repository will track when and by whom changes are made to the record. Of course, there are some issues with this, but I think it could be made to work well. >Hibernate does this, more or less, for Java classes. That might be a >good place to look for ideas. Good point. I'll start there. [1] http://www.codeproject.com/KB/database/DatabaseSchemaVersioning.aspx --Jonathan On Sat, Sep 25, 2010 at 3:45 PM, Rogan Creswick wrote: > On Sat, Sep 25, 2010 at 12:31 PM, Jonathan Geddes > wrote: >> >> Does such a thing exist? If not, would you find it useful? I may take >> this up as a side project if it does not already exist and others >> would find it useful. >> > > I've been looking for something along these lines too. > > Hibernate does this, more or less, for Java classes. That might be a > good place to look for ideas. > > --Rogan > >> Thanks, >> >> --Jonathan >> ___ >> 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: Shared thunk optimization. Looking to solidify my understanding
On 9/25/10 3:43 PM, Jan-Willem Maessen wrote: No one seems to have mentioned that this is a non-optimization in call-by-need lambda-calculus (Ariola et al.), where it follows from the standard reduction rules. Exactly. Then again, call-by-need gives a form of partial evaluation, which was what I was pointing out in in the post described as: On Wed, Sep 22, 2010 at 11:10 AM, David Sankel wrote: wren ng thornton provided an evaluation using another operational semantics (reference?). Under this semantics, this optimization would be called partial evaluation. Unfortunately I couldn't follow the steps or the reasoning behind them, perhaps a reference to the semantics would help. -- Live well, ~wren ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Simple question about the function composition operator
On 9/24/10 5:35 AM, Axel Benz wrote: Can anybody explain why this happens and how I can compose f and g? Hint: It works fine if f is defined as an unary function. As already mentioned: (g . f) x y = (\z-> g (f z)) x y = g (f x) y In order to get it to work you need to say that you want to pass two arguments to f. The immediate answer is ((g .) . f) but that doesn't really give you a general pattern to use. The general pattern is, -- | Binary composition. (...) :: (c -> d) -> (a -> b -> c) -> (a -> b -> d) (...) = (.) . (.) {-# INLINE (...) #-} infixl 8 ... and then (g ... f) x y = g (f x y). Note that the fixity is set up so that (...) plays nicely with (.). You may also be interested in, -- | Compose on second arg. (.^) :: (a -> c -> d) -> (b -> c) -> (a -> b -> d) (.^) = flip ... (.) . flip {-# INLINE (.^) #-} infix 9 .^ -- | Function composition which calls the right-hand -- function eagerly. (.!) :: (b -> c) -> (a -> b) -> a -> c (.!) = (.) . ($!) {-# INLINE (.!) #-} infixr 9 .! -- Live well, ~wren ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Inverse of HaskellDB
Versioning is a tricky problem regardless of how you are creating tables. And that isn't the problem I was aiming to tackle; the problem I was aiming to tackle is a bit more narrow than that: I have a record and now I need a table to stick it in. By the way, how does HaskellDB handle versioning? --Jonathan On Sat, Sep 25, 2010 at 1:57 PM, Antoine Latter wrote: > That sounds pretty awesome to me. > > Have you given any thought as to how you want to approach versioning? > > Maybe I'm asking a silly question - I have very little real world experience > with relation databases and how to version schemas. > > Antoine > > On Sep 25, 2010 2:31 PM, "Jonathan Geddes" > wrote: >> Cafe, >> >> HaskellDB takes a database schema and produces Haskell data structures >> (plus some other query-related stuff for its EDSL query language). >> >> What I'm looking for is the inverse of this functionality. I want to >> create tables based on a Haskell data structure with a few simple >> rules. These rules include: if a field is not of the form `Maybe a' >> then it can't be nullable in the database. If a field is not a >> primitive (in the database) then it is actually stored in another >> table and a reference id is stored in the table. Tables are produced >> recursively, unless they already exist, etc. >> >> The HaskellDB approach is great for interfacing with existing tables, >> but in my case I already have data structures and now I would like a >> quick way to create tables to persist them. >> >> Does such a thing exist? If not, would you find it useful? I may take >> this up as a side project if it does not already exist and others >> would find it useful. >> >> Thanks, >> >> --Jonathan >> ___ >> 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] Inverse of HaskellDB
That sounds pretty awesome to me. Have you given any thought as to how you want to approach versioning? Maybe I'm asking a silly question - I have very little real world experience with relation databases and how to version schemas. Antoine On Sep 25, 2010 2:31 PM, "Jonathan Geddes" wrote: > Cafe, > > HaskellDB takes a database schema and produces Haskell data structures > (plus some other query-related stuff for its EDSL query language). > > What I'm looking for is the inverse of this functionality. I want to > create tables based on a Haskell data structure with a few simple > rules. These rules include: if a field is not of the form `Maybe a' > then it can't be nullable in the database. If a field is not a > primitive (in the database) then it is actually stored in another > table and a reference id is stored in the table. Tables are produced > recursively, unless they already exist, etc. > > The HaskellDB approach is great for interfacing with existing tables, > but in my case I already have data structures and now I would like a > quick way to create tables to persist them. > > Does such a thing exist? If not, would you find it useful? I may take > this up as a side project if it does not already exist and others > would find it useful. > > Thanks, > > --Jonathan > ___ > 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: Shared thunk optimization. Looking to solidify my understanding
No one seems to have mentioned that this is a non-optimization in call-by-need lambda-calculus (Ariola et al.), where it follows from the standard reduction rules. Since lazy implementations of Haskell all use call-by-need evaluation in some form, I'd call this "playing by the rules" rather than "optimization". Unoptimized call-by-need indeed evaluates (nthPrime 10) twice in test2, but only once in test1. (Challenge: prove observationl equivalence of these two fragments under call-by-need.) -Jan-Willem Maessen On Fri, Sep 24, 2010 at 5:58 PM, David Sankel wrote: > On Wed, Sep 22, 2010 at 11:10 AM, David Sankel wrote: >> >> >> My questions are: >> >> What is the optimization that test1 is taking advantage of called? >> Is said optimization required to conform to the Haskell98 standard? If so, >> where is it stated? >> Could someone explain or point to a precise explanation of this >> optimization? If I'm doing an operational reduction by hand on paper, how >> would I take account for this optimization? > > Thanks everyone for your responses. I found them very helpful. This is my > current understanding, please correct me where I am wrong: > When using Launchbury's Natural Semantics (LNS) as an operational model, > this optimization is called sharing which would lie in a category of > optimizations called common subexpression elimination. Holger Siegel's email > provided steps of an evaluation using LNS to show the different runtimes > between test1 and test2. > Because Haskell98 does not specify an operational semantics, there is > no guarantee that an implementation will provide a sharing optimization. On > the other hand, Haskell implementations are all similar enough that the > sharing optimization can be depended on. LNS was indeed written to model > what is common in implementations for languages characteristically like > Haskell. > When compiled with ghc with optimizations, test1 and test2 result in > identical runtime behaviors. This is an artifact of another, more > aggressive, optimization that falls within common subexpression elimination > optimizations. It is not easy to describe or predict when this optimization > occurs so depending on it when writing code is problematic. > wren ng thornton provided an evaluation using another operational semantics > (reference?). Under this semantics, this optimization would be called > partial evaluation. Unfortunately I couldn't follow the steps or the > reasoning behind them, perhaps a reference to the semantics would help. > Thanks again! > > David > -- > David Sankel > Sankel Software > www.sankelsoftware.com > 585 617 4748 (Office) > > ___ > 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] Inverse of HaskellDB
Cafe, HaskellDB takes a database schema and produces Haskell data structures (plus some other query-related stuff for its EDSL query language). What I'm looking for is the inverse of this functionality. I want to create tables based on a Haskell data structure with a few simple rules. These rules include: if a field is not of the form `Maybe a' then it can't be nullable in the database. If a field is not a primitive (in the database) then it is actually stored in another table and a reference id is stored in the table. Tables are produced recursively, unless they already exist, etc. The HaskellDB approach is great for interfacing with existing tables, but in my case I already have data structures and now I would like a quick way to create tables to persist them. Does such a thing exist? If not, would you find it useful? I may take this up as a side project if it does not already exist and others would find it useful. Thanks, --Jonathan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] ANN: JMacro 0.3.2, A library/dsl for generating Javascript
JMacro on hackage: http://hackage.haskell.org/package/jmacro This is the first official release announcement for JMacro, which has been on hackage in some form for over a year, and in the current version since July. JMacro is a library for the programmatic generation of Javascript code. It is designed to be multipurpose -- it is useful whether you are writing nearly vanilla Javascript or you are programmatically generating Javascript either in an ad-hoc fashion or as the backend to a compiler or EDSL. It provides support for hygienic names, as well as sharing of names between the generated Javascript and embedded Haskell antiquotation. In this release it also includes a module which allows the generation of RPC request/response pairs, allowing a lightweight implementation of AJAX-heavy applications. JMacro provides a simple, lightweight quasiquoted syntax that is mainly compatible with standard Javascript. Most Javascript code in the wild can be used as JMacro code with no or minimal modification. However, JMacro extends Javascript syntax in a number of Haskell-friendly ways, including whitespace function application and single character lambdas. Syntax is statically checked at compile time. JMacro expressions may contain antiquoted Haskell code. This code may generate further JMacro code, or it may generate any of a range of standard Haskell types, which are able to be marshalled into JMacro through typeclass methods. JMacro also provides an executable, which allows the standalone processing of JMacro code into Javascript. For more information, see both Hackage and the JMacro documentation on the HaskellWiki: http://www.haskell.org/haskellwiki/Jmacro Some examples or idiomatic JMacro code are available in the source of its provided Javascript Prelude: http://hackage.haskell.org/packages/archive/jmacro/0.3.2/doc/html/src/Language-Javascript-JMacro-Prelude.html#jmPrelude Future work on JMacro, when time is available, is geared towards providing an optional layer of static typing with type inference. Patches, bug reports, and feature requests are all very welcome. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Candlestick charts
On Sat, 25 Sep 2010, rgowka1 wrote: I am trying to compile demo.hs, but keep getting the error that Paths_gnuplot could not be found. What/where is paths_gnuplot?? Sorry, I am still a beginner.. I forgot to mention in the documentation that you have to install with $ cabal install -fbuildExamples gnuplot in order to get the Demo compiled and the example data file installed. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Applicative instances for Monads
On Sat, Sep 25, 2010 at 3:01 AM, Gregory Crosswhite wrote: > == > > import Control.Applicative > import Control.Concurrent > import Control.Concurrent.MVar > > newtype AIO a = AIO {unAIO :: IO a} > > instance Monad AIO where > return = AIO . return > (AIO x) >>= f = AIO (x >>= unAIO . f) > > instance Functor AIO where > fmap f (AIO x) = AIO (fmap f x) > > instance Applicative AIO where > pure = return > (AIO mf) <*> (AIO ma) = AIO $ do > f_box <- newEmptyMVar > forkIO (mf >>= putMVar f_box) > a_box <- newEmptyMVar > forkIO (ma >>= putMVar a_box) > f <- takeMVar f_box > a <- takeMVar a_box > return (f a) > > == This idea is pretty neat :) I think it should be found a place on the wiki, or maybe even Hackage. The way in which it interacts with exceptions, especially async exceptions, could be odd though, so it'd be worth checking it pedantically adheres to the rules. > To summarize: on the one hand every Monad has a generic instance for > Applicative, and yet on the other hand this instance is often arguably not > the "correct" one because it ignores the fact that the second computation is > independent of the first, which is a fact that can be exploited given > additional knowledge about the structure of the Monad. > > I bring this up because there has been talk here of automatically having > instances of Monad also be instances of Applicative, and what bugs me is > that on the one hand this makes perfect since as every Monad can also be > viewed as an Applicative, and yet on the other hand not only is there often > more than one natural way to define an Applicative instance for selected > Monads but furthermore the "generic" instance is often an inferior > definition because it ignores the structure of the Monad. I think what we learn from this is not that the Monad-based instance of Applicative is necessarily the "wrong" one, but rather that there is often more than one reasonable instance for a type, each suitable for different uses. There are times when parallelisation is not a priority, but determinism is, in which case we'd *want* the sequencing of Monad even in the Applicative instance. Often we use newtypes to distinguish between them (see: ZipList), and if we accept that the Monad-based instance is always a useful one (and if the Monad instance itself is useful I think it is) it makes sense for it also to be the "default" one, so that we can have ap and <*> always mean the same thing in the same context. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Coding conventions for Haskell?
On Sat, Sep 25, 2010 at 5:06 PM, Donn Cave wrote: > Though it's common practice for sure, maybe universal, does the > "Don't insert a space after a lambda" rule make sense? > > I found it confusing at first sight, because of course it looks > like something else - in "\n m -> ...", to the uninitiated it > represents a newline, for example. Now that I understand that > it's a symbolic keyword, it's an odd way to treat it. This has > probably come up before, so feel free to ignore, "I'm just saying." I think I lean more towards surrounding "\" with spaces nowadays. > The white space I have trouble deciding on is one-line record > syntax -- ARecord { aField = "a" }, or maybe ARecord {aField = "a"}. I always do the former and I think it's the more common style. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Coding conventions for Haskell?
Though it's common practice for sure, maybe universal, does the "Don't insert a space after a lambda" rule make sense? I found it confusing at first sight, because of course it looks like something else - in "\n m -> ...", to the uninitiated it represents a newline, for example. Now that I understand that it's a symbolic keyword, it's an odd way to treat it. This has probably come up before, so feel free to ignore, "I'm just saying." The white space I have trouble deciding on is one-line record syntax -- ARecord { aField = "a" }, or maybe ARecord {aField = "a"}. Donn ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Tree Construction
Am 25.09.2010 um 11:54 schrieb Tom Hawkins: > Hi, > > Often I need to assemble a tree from things with unstructured > hierarchical paths. I built a function [1] to do this for ImProve. > But does a library already exist that does this? If not I may create > one, as I need it for a few different libraries. > > data Tree a b = Branch a [Tree a b] | Leaf a b > > tree :: (Eq a, Ord a) => (b -> [a]) -> [b] -> [Tree a b] > > Note, type 'a' is some sort of label, most often a string, and type > 'b' form the leaves of the tree. The function passed into 'tree' > returns the hierarchical path of a leaf object. > > -Tom > > [1] > http://hackage.haskell.org/packages/archive/improve/0.0.12/doc/html/Language-ImProve-Tree.html As Sjoerd Visscher has pointed out, this data structure is called trie. Here is a version of your module that allows for empty paths, uses sets instead of lists and stores values and subtrees separately: module Language.ImProve.Tree ( Tree (..), tree) where import qualified Data.Map as Map import Data.Monoid data Tree a b = Tree [b] (Map.Map a (Tree a b)) instance Ord a => Monoid (Tree a b) where mempty = Tree [] Map.empty mappend (Tree vs1 sts1) (Tree vs2 sts2) = Tree (vs1 ++ vs2) (Map.unionWith mappend sts1 sts2) tree :: Ord a => (b -> [a]) -> [b] -> Tree a b tree path leaves = mconcat [ foldr branch (leaf l) (path l) | l <- leaves ] where leaf a = Tree [a] Map.empty branch b t = Tree [] (Map.singleton b t) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Candlestick charts
I am trying to compile demo.hs, but keep getting the error that Paths_gnuplot could not be found. What/where is paths_gnuplot?? Sorry, I am still a beginner.. On Sat, Sep 25, 2010 at 8:48 AM, Henning Thielemann wrote: > > On Sat, 25 Sep 2010, rgowka1 wrote: > >> Can I just do cabal install gnuplot or should I use darcs to get the >> candles version.. > > The Hackage version should be up to date now. > ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Tree Construction
Hi, I think what you need is a trie. See f.e. http://hackage.haskell.org/package/list-tries On Sep 25, 2010, at 11:54 AM, Tom Hawkins wrote: > Hi, > > Often I need to assemble a tree from things with unstructured > hierarchical paths. I built a function [1] to do this for ImProve. > But does a library already exist that does this? If not I may create > one, as I need it for a few different libraries. > > data Tree a b = Branch a [Tree a b] | Leaf a b > > tree :: (Eq a, Ord a) => (b -> [a]) -> [b] -> [Tree a b] > > Note, type 'a' is some sort of label, most often a string, and type > 'b' form the leaves of the tree. The function passed into 'tree' > returns the hierarchical path of a leaf object. > > -Tom > > [1] > http://hackage.haskell.org/packages/archive/improve/0.0.12/doc/html/Language-ImProve-Tree.html > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Sjoerd Visscher http://w3future.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Candlestick charts
On Sat, 25 Sep 2010, rgowka1 wrote: Can I just do cabal install gnuplot or should I use darcs to get the candles version.. The Hackage version should be up to date now. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Candlestick charts
Can I just do cabal install gnuplot or should I use darcs to get the candles version.. On Sat, Sep 25, 2010 at 8:03 AM, Henning Thielemann wrote: > > On Sat, 25 Sep 2010, rgowka1 wrote: > >> Hi - >> >> What are the libraries to use in Haskell to generate a stock >> candlestick chart like >> http://stockcharts.com/h-sc/ui?s=SPY&p=D&b=5&g=5&id=p05007254056 >> >> I will use Finance-Quote-Yahoo to get the quote data from Yahoo. > > You might try the gnuplot package as interface to the gnuplot program. > > There was already someone who wanted to plot candle sticks: > http://projects.haskell.org/pipermail/gnuplot/2010-April/09.html > ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Candlestick charts
On Sat, 25 Sep 2010, rgowka1 wrote: Hi - What are the libraries to use in Haskell to generate a stock candlestick chart like http://stockcharts.com/h-sc/ui?s=SPY&p=D&b=5&g=5&id=p05007254056 I will use Finance-Quote-Yahoo to get the quote data from Yahoo. You might try the gnuplot package as interface to the gnuplot program. There was already someone who wanted to plot candle sticks: http://projects.haskell.org/pipermail/gnuplot/2010-April/09.html ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Candlestick charts
Hi - What are the libraries to use in Haskell to generate a stock candlestick chart like http://stockcharts.com/h-sc/ui?s=SPY&p=D&b=5&g=5&id=p05007254056 I will use Finance-Quote-Yahoo to get the quote data from Yahoo. thanks for all your help. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Coding conventions for Haskell?
On Sat, Sep 25, 2010 at 11:24 AM, Petr Pudlak wrote: > sometimes I have doubts how to structure my Haskell code - where to break > lines, how much to indent, how to name functions and variables etc. Are > there any suggested/recommended coding conventions? I searched a bit and I > found a few articles and discussions: Quite a few people follow my style guide http://github.com/tibbe/haskell-style-guide/blob/master/haskell-style.md which codifies the style used in Real World Haskell, bytestring, text, and a few other libraries. -- Johan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Tree Construction
Hi, Often I need to assemble a tree from things with unstructured hierarchical paths. I built a function [1] to do this for ImProve. But does a library already exist that does this? If not I may create one, as I need it for a few different libraries. data Tree a b = Branch a [Tree a b] | Leaf a b tree :: (Eq a, Ord a) => (b -> [a]) -> [b] -> [Tree a b] Note, type 'a' is some sort of label, most often a string, and type 'b' form the leaves of the tree. The function passed into 'tree' returns the hierarchical path of a leaf object. -Tom [1] http://hackage.haskell.org/packages/archive/improve/0.0.12/doc/html/Language-ImProve-Tree.html ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Coding conventions for Haskell?
Hi, sometimes I have doubts how to structure my Haskell code - where to break lines, how much to indent, how to name functions and variables etc. Are there any suggested/recommended coding conventions? I searched a bit and I found a few articles and discussions: - Good Haskell coding standards from Stackoverflow http://stackoverflow.com/questions/1983047/good-haskell-coding-standards - Programming guidelines from Haskellwiki http://www.haskell.org/haskellwiki/Programming_guidelines - How to read Haskell from Haskellwiki (this is actually about reading, not composing code, but still worth reading) http://www.haskell.org/haskellwiki/How_to_read_Haskell - Good Haskell Style http://urchin.earth.li/~ian/style/haskell.html but they usually address only a few specifics. I was looking for something more complete and comprehensive. Perhaps something like Java has [1]. Any suggestions? Best regards, Petr [1] http://www.oracle.com/technetwork/java/codeconv-138413.html ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] parsec manyTill documentation question
On 25 September 2010 05:30, Evan Laforge wrote: > I thought the parsec source included some example parsers for simple > languages? In any case, there is lots of material floating around, > [Snip] The best documentation is Daan Leijen's original manual, plus the original source distribution which has example parsers for Henk, Tiger and Mondrain. Both are available from here - the original poster was working with the HTML version of the manual - there is also a PDF version: http://legacy.cs.uu.nl/daan/parsec.html It would be nice if the Hackage package added the examples back into the distribution. The parser in the Scheme in 48 hours tutorial isn't a great example of Parsec as it doesn't use the Token module. Not using the Token module means the Scheme parser does hacky things such as parseNumber which uses /read/ - this is double work, Parsec already handles numbers, it doesn't need to call out to another parser (Haskell's builtin read). http://en.wikibooks.org/wiki/Write_Yourself_a_Scheme_in_48_Hours/Parsing ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe