Re: [Haskell-cafe] [Snap] Argument Substitution in Heist Templates with Splices

2012-09-23 Thread Sebastian Fischer
Thanks! For the record, here is how to achieve what I want by
explicitly using `runChildren` and `stopRecursion`:

testSplice :: Splice IO
testSplice = do
input <- getParamNode
kids <- runChildren
stopRecursion
return [input { elementChildren = kids }]

It surprises me that an explicit call to `runChildren` is necessary,
especially after your comment regarding sensitivity to evaulation
order.

Your linked post shows that Heist splices are processed top down,
which reminds me of the `transform` combinator in Uniplate:


http://community.haskell.org/~ndm/downloads/paper-uniform_boilerplate_and_list_processing-30_sep_2007.pdf

The authors discuss bottom-up and top-down transformations in Sections
2.3 and 2.4 and argue for providing bottom-up transformations and only
a specific form of top-down transformations.

I think Heist's splice processing would be more intuitive (less
sensitive to evaluation order?) if applied bottom up rather than top
down. This only seems to require a slight change in the definition of
`runNode` from the post you linked - to process children before
applying the splice:

runNode :: Monad m => X.Node -> Splice m
runNode (X.Element nm at ch) = do
newAtts <- mapM attSubst at
newKids <- runNodeList ch  -- added this line
let n = X.Element nm newAtts newKids -- changed this line
s <- liftM (lookupSplice nm) getTS
maybe n (recurseSplice n) s  -- changed this line
  -- removed local function `runKids`
runNode n= return [n]

This change would simplify the definition of filter splices which
would not need to call `runChildren` explicitly. It would also make
the definition of substitution splices more uniform, because children
would be already processed when applying the splice - just like
attributes are.

Are Heist splices processed top down intentionally? (Reasons for doing
so are the same reasons people might have for preferring call-by-name
over call-by-value. However, I tend to agree with the discussion in
the Uniplate paper and would prefer "call-by-value" aka bottom-up
transformation.)

Best,
Sebastian

On Fri, Sep 21, 2012 at 6:03 PM, MightyByte  wrote:
> This is one of the more subtle corner cases of Heist.  My default, splices
> are recursively processed.  So when testSplice is executed for the 
> tag, the results are fed back into splice processing.  I think this is the
> right thing to do because it makes behavior less sensitive to evaluation
> order.  Obviously this can lead to infinite recursion, so Heist limits the
> splice call stack to a depth of 50.  If this limit is exceeded, then Heist
> simply stops recursing and returns the nodes unprocessed.  I also think this
> is the right thing to do because it is happening as we're serving a page to
> the end user, so there's an argument for failing quietly instead of going up
> in a ball of flames.
>
> In your case, you are returning the same node that was spliced in, so you
> are hitting the recursion limit and splice processing just stops.  I discuss
> this issue in my blog post about splice subtleties
> (http://softwaresimply.blogspot.com/2011/04/splice-subtleties.html).  Since
> you're writing a filter splice, you need to call stopRecursion.  But if you
> do that, then the child  tag won't be processed.  So what you need to
> do is use the runChildren function to process the child nodes, then return
> them in whatever your constructed node is.
>
> I think the easiest solution to your problem is to not write it as a filter
> splice.  Bind your testSplice function to the  tag and return a
>  tag.  This avoids the infinite recursion and will work the way you
> want without needing stopRecursion.
>
> On Thu, Sep 20, 2012 at 3:00 PM, Sebastian Fischer  wrote:
>>
>> Hello,
>>
>> the following program demonstrates that arguments in Heist templates
>> are sometimes not substituted in presence of splices:
>>
>> {-# LANGUAGE OverloadedStrings #-}
>>
>> import   Blaze.ByteString.Builder (toByteString)
>> import qualified Data.ByteString.Char8as BS
>> import   Data.Functor ((<$>))
>> import   Data.Maybe   (fromJust)
>> import   Text.Templating.Heist
>>
>> -- just return input node unchanged
>> testSplice :: Splice IO
>> testSplice = (:[]) <$> getParamNode
>>
>> main = do
>> writeFile "test.tpl" ""
>> state <- either error id <$> loadTemplates "." defaultHeistState
>>
>> (builder,_) <- fromJust <$> renderWithArgs [("arg","42")] state "test"
>> BS.putStrLn $ toByteString builder
>> -- 4242
>>
>> let state' = bindSplices [("test",testSplice)] state
>> (builder',_) <- fromJust <$> renderWithArgs [("arg","42")] state'
>> "test"
>> BS.putStrLn $ toByteString builder'
>> -- 42
>>
>> Without using splices, all occurrences of 'arg' in the template are
>> substituted. When using a splice, 'arg' is not substituted underneath
>> the input node of the splice. It is substituted in an attribute of the
>>

Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-23 Thread Heinrich Apfelmus

Michael Snoyman wrote:

(Prettier formatting available at: https://gist.github.com/3761252)

Many of us use the OverloadedStrings language extension on a regular
basis. It provides the ability to keep the ease-of-use of string
literal syntax, while getting the performance and correctness
advantages of specialized datatypes like ByteString and Text. I think
we can get the same kind of benefit by allowing another literal syntax
to be overloaded, namely lists.


Actually, I am already somewhat reserved about the  OverloadedStrings 
proposal.


The core point of the OverloadedSomething extensions is that they 
address a syntactic issue, namely that we can write


  "example"

instead of

  (pack "example")

The extension does this by making the literal polymorphic.

Unfortunately, making literals polymorphic does not always achieve the 
desired effect of reducing syntax. In fact, they can instead increase 
syntax! In other words, I would like to point out that there is a 
trade-off involved: is it worth introducing a small syntactic reduction 
at the cost of both a small additional conceptual complexity and some 
syntactic enlargement elsewhere?



The increase in syntax happened to me while using one of the json 
libraries. The thing is that if a "receiver" function is agnostic in the 
string used, or if it is otherwise polymorphic,


receive1 :: IsString s => s -> Foo
receive2 :: JSON s => s -> Foo

then I have to specify the type of the overloaded argument (either by a 
type annotation or a monomorphic function call).


In other words, without  OverloadedStrings , I was able to write

receive2 "example"

but with the extension, I now have to write

receive2 (pack "example")


A similar effect can be seen with the good old numeric literals. 
Sometimes, you just have to introduce a type signature (:: Int) to make 
a program unambiguous.



In this light, I don't think that the trade-off made by the 
OverloadedLists extension is big enough.



Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


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


[Haskell-cafe] Organizaing tests in Haskell

2012-09-23 Thread Jan Stolarek
Dear list,

during many years of Java programming I've been faithful to TDD methology. 
Recently I've been 
trying to figure out how to do tests in Haskell. Thanks to RWH and help from 
great folks at 
#haskell I've managed to get on my feet. There is however one issue I wasn't 
able to solve.

In Java it is very easy to separate test code from the actual source. A Java 
project simply 
contains two folders: src and tests. These two are treated as the source 
directories. Both these 
directories have the same subdirectory structure. For example I have a source 
file 
src/myPackage/mySubpackage/MyClass.java and test for it are kept in file 
tests/myPackage/mySubpackage/MyClassTest.java. These two files are considered 
by Java to be in 
the same package. Here's the main trick: fileds and methods that are marked as 
protected in Java 
are accessible to other classes in the same package. This allows to test 
internal methods of a 
class by marking them as protected instead of private. This breaks 
encapsulation but only within 
a package, which is acceptable.

Now I'd like to achieve something similar in Haskell. I'm using cabal's support 
for testing. I 
created separate src and tests directories, both with the same subdirectory 
structure. I keep 
tests for each module in a separate file (e.g. I have src/Math/MyModule.hs and 
tests/Math/MyModuleTest.hs) and I have one file that assembles all the tests 
into a single test 
suite (I use test-framework for that). The only problem is that in order to 
test some function 
from a module I have to expose that function, which pretty much forces me to 
give up on 
encapsulation.

Is there any better solution to organize tests in Haskell? Should I just give 
up on module 
encapsulation, or should I only test functions exposed by the module and don't 
worry about 
internal functions? Perhaps I should use some different approach?

Jan

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


Re: [Haskell-cafe] Organizaing tests in Haskell

2012-09-23 Thread Simon Hengel
Hi,

> Is there any better solution to organize tests in Haskell?

(Disclaimer: I'm the maintainer of Hspec ;)

If you use Hspec[1] for testing, you do not have to assemble your
individual tests manually into a test suit; hspec-discover[2] takes care
of that.

There is no comprehensive user's guide for Hspec yet, but a basic
introduction is at [3].  If you have any questions, feel free to join in
at #hspec on freenode.

> Should I just give up on module encapsulation, or should I only test
> functions exposed by the module and don't worry about internal
> functions?

You can do it with CPP.  Say, if you have a module Foo, with functions
foo, bar and baz, where baz  is not part of the public interface, then
the export list becomes:


{-# LANGUAGE CPP #-}
module Foo where (
  foo
, bar
#ifdef TEST
, baz
#endif
)

You then run tests with -DTEST.  To make development easier you can add
a .ghci file to your project, with:

echo ':set -DTEST -isrc -itest' > .ghci

And of course you need to add 

cpp-options: -DTEST

to your Cabal test-suite section.

Cheers,
Simon

[1] http://hackage.haskell.org/package/hspec
[2] 
https://github.com/hspec/hspec/tree/master/hspec-discover#automatically-discover-and-run-hspec-tests
[3] http://hspec.github.com/

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


Re: [Haskell-cafe] Organizaing tests in Haskell

2012-09-23 Thread Matthew West

On 23 Sep 2012, at 10:25, Jan Stolarek wrote:

> Dear list,
> 
> during many years of Java programming I've been faithful to TDD methology. 
> Recently I've been 
> trying to figure out how to do tests in Haskell. Thanks to RWH and help from 
> great folks at 
> #haskell I've managed to get on my feet. There is however one issue I wasn't 
> able to solve.
> 
> In Java it is very easy to separate test code from the actual source. A Java 
> project simply 
> contains two folders: src and tests. These two are treated as the source 
> directories. Both these 
> directories have the same subdirectory structure. For example I have a source 
> file 
> src/myPackage/mySubpackage/MyClass.java and test for it are kept in file 
> tests/myPackage/mySubpackage/MyClassTest.java. These two files are considered 
> by Java to be in 
> the same package. Here's the main trick: fileds and methods that are marked 
> as protected in Java 
> are accessible to other classes in the same package. This allows to test 
> internal methods of a 
> class by marking them as protected instead of private. This breaks 
> encapsulation but only within 
> a package, which is acceptable.
> 
> Now I'd like to achieve something similar in Haskell. I'm using cabal's 
> support for testing. I 
> created separate src and tests directories, both with the same subdirectory 
> structure. I keep 
> tests for each module in a separate file (e.g. I have src/Math/MyModule.hs 
> and 
> tests/Math/MyModuleTest.hs) and I have one file that assembles all the tests 
> into a single test 
> suite (I use test-framework for that). The only problem is that in order to 
> test some function 
> from a module I have to expose that function, which pretty much forces me to 
> give up on 
> encapsulation.
> 
> Is there any better solution to organize tests in Haskell? Should I just give 
> up on module 
> encapsulation, or should I only test functions exposed by the module and 
> don't worry about 
> internal functions? Perhaps I should use some different approach?
> 
> Jan
> 
Hi,
  From looking at other packages on Hackage a common trick seems to be to 
create some internal modules, 
then have an external module that simply exposes the 'public' functions.  Your 
internal tests can then import 
the internal modules, and your API tests can import the external module.  Of 
course others are still able to import 
your Internal modules, but you have at least made it clear that that is a bad 
idea.

for example:

MyLib/Internal/Lib.hs:

module MyLib.Internal.Lib where -- exports all the functions defined in this 
function
internalFunction = ...
externalFunction = ...

MyLib/Lib.hs
module MyLib.Lib (   -- exports only the public functions
externalFunction
)
where
import MyLib.Internal.Lib  -- imports all the internal functions

test/Internal/Lib.hs
...
import MyLib.Internal.Lib
...

test/Lib.hs
...
import MyLib.Lib   -- imports only the public API
...

Yesod is an example of a large project using this approach, for example 
https://github.com/yesodweb/yesod/tree/master/yesod-core

Matt


> ___
> 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] Organizaing tests in Haskell

2012-09-23 Thread Simon Hengel
> Of course others are still able to import your Internal modules

That is not necessarily true.  For libraries, you can list internal
modules as other-modules (in contrast to exposed-modules) in you Cabal
file.  That way they are not part of the public interface of your
library.

However, that approach does not work if you want to do encapsulation
within a single project.  I think in that case you most likely end up
with CPP (it's ugly, but it works).

Cheers,
Simon

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


Re: [Haskell-cafe] Platform Versioning Policy: upper bounds are not our friends

2012-09-23 Thread Alberto G. Corona
Just thinking  aloud:

What if  we add  "-current"  ?

pacage -current

Would select the versions of the package that were current art the time the
cabal file was uploaded and sucessfully compiled in hackage,  if the packae
is installed from hackage

If the cabal file is local then current == any.

This option would eliminate the need to guess bounds for package
dependencies. It would also give more guaranties that the package will
compile sucessfully when downloaded from hackage.

Certainly,it would not guarantee it if your version of ghc differs from the
one in Hackage, but it would make things more simple and would reduce the
spectrum of possible failures


2012/8/24 wren ng thornton 

> On 8/22/12 12:35 PM, David Menendez wrote:
>
>> As I see it, there are four possibilities for a given version of
>> dependency:
>>
>> 1. The version DOES work. The author (or some delegate) has compiled
>> the package against this version and the resulting code is considered
>> good.
>> 2. The version SHOULD work. No one has tested against this version,
>> but the versioning policy promises not to break anything.
>> 3. The version MIGHT NOT work. No one has tested against this version,
>> and the versioning policy allows breaking changes.
>> 4. The version DOES NOT work. This has been tested and the resulting
>> code (if any) is considered not good.
>>
>> Obviously, cases 1 and 4 can only apply to previously released
>> versions. The PVP requires setting upper bounds in order to
>> distinguish cases 2 and 3 for the sake of future compatibility.
>> Leaving off upper bounds except when incompatibility is known
>> essentially combines cases 2 and 3.
>>
>
> Right-o.
>
>
>
>  So there are two failure modes:
>>
>> I. A version which DOES work is outside the bounds (that is, in case
>> 3). I think eliminating case 3 is too extreme. I like the idea of
>> temporarily overriding upper bounds with a command-line option. The
>> danger here is that we might actually be in case 4, in which case we
>> don't want to override the bounds, but requiring an explicit override
>> gives users a chance to determine if a particular version is
>> disallowed because it is untested or because it is known to be
>> incompatible.
>>
>
> There are two failure modes with overriding stated bounds, however. On the
> one hand, the code could fail to compile. Okay, we know we're in case 4;
> all is well. On the other hand the code could successfully compile in ways
> the package designer knows to be buggy/wrong; we're actually in case 4, but
> the user does not know this. This is why it's problematic to simply allow
> overriding constraints. The package developer has some special knowledge
> that the compiler lacks, but if all constraints are considered equal then
> the developer has no way to convey that knowledge to the user (i.e., in an
> automated machine-checkable way). Consequently, the user can end up in a
> bad place because they thought this second failure mode was actually the
> success mode.
>
> This is why I advocate distinguishing hard constraints from soft
> constraints. By making this distinction, the developer has a means of
> conveying their knowledge to users. A soft bound defines an explicit
> boundary between case 1 and cases 2--4, which can be automatically (per
> PVP) extended to an implicit boundary between cases 1--2 and cases 3--4; a
> boundary which, as you say, can only be truly discovered after the code has
> been published. Extending soft boundaries in this way should be safe; at
> least it's as safe as possible with the foresight available to us. On the
> other hand, a hard bound defines an explicit boundary between case 4 and
> cases 1--3. If these are overridable, things may break silently as
> discussed above--- but the important thing is, in virtue of distinguishing
> hard and soft bounds, the user is made aware of this fact. By
> distinguishing hard and soft bounds, the developer can convey their special
> knowledge to the user. The user can ignore this information, but at least
> they'll do so in an informed way.
>
>
> --
> Live well,
> ~wren
>
> __**_
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/**mailman/listinfo/haskell-cafe
>



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


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-23 Thread Michael Snoyman
On Sun, Sep 23, 2012 at 10:51 AM, Heinrich Apfelmus
 wrote:
> Michael Snoyman wrote:
>>
>> (Prettier formatting available at: https://gist.github.com/3761252)
>>
>> Many of us use the OverloadedStrings language extension on a regular
>> basis. It provides the ability to keep the ease-of-use of string
>> literal syntax, while getting the performance and correctness
>> advantages of specialized datatypes like ByteString and Text. I think
>> we can get the same kind of benefit by allowing another literal syntax
>> to be overloaded, namely lists.
>
>
> Actually, I am already somewhat reserved about the  OverloadedStrings
> proposal.
>
> The core point of the OverloadedSomething extensions is that they address a
> syntactic issue, namely that we can write
>
>   "example"
>
> instead of
>
>   (pack "example")
>
> The extension does this by making the literal polymorphic.
>
> Unfortunately, making literals polymorphic does not always achieve the
> desired effect of reducing syntax. In fact, they can instead increase
> syntax! In other words, I would like to point out that there is a trade-off
> involved: is it worth introducing a small syntactic reduction at the cost of
> both a small additional conceptual complexity and some syntactic enlargement
> elsewhere?
>
>
> The increase in syntax happened to me while using one of the json libraries.
> The thing is that if a "receiver" function is agnostic in the string used,
> or if it is otherwise polymorphic,
>
> receive1 :: IsString s => s -> Foo
> receive2 :: JSON s => s -> Foo
>
> then I have to specify the type of the overloaded argument (either by a type
> annotation or a monomorphic function call).
>
> In other words, without  OverloadedStrings , I was able to write
>
> receive2 "example"
>
> but with the extension, I now have to write
>
> receive2 (pack "example")
>
>
> A similar effect can be seen with the good old numeric literals. Sometimes,
> you just have to introduce a type signature (:: Int) to make a program
> unambiguous.
>
>
> In this light, I don't think that the trade-off made by the OverloadedLists
> extension is big enough.
>
>
> Best regards,
> Heinrich Apfelmus
>
> --
> http://apfelmus.nfshost.com
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

I agree with your point. But what you've pointed out is that there's a
trade-off involved, and then elaborated on the downsides of the
trade-off. Let's not forget that there are significant upsides as
well. And based on the large amount of code out there that actually
uses OverloadedStrings, I think many people feel that the upsides
outweigh the downsides in many cases. The nice thing about an
extension like OverloadedStrings or OverloadedLists is that it need
not affect your code in any way: if you don't turn it on, your code
will continue to work. And you'll still be able to use libraries that
themselves use the extensions without any ill effects.

That said, it would be great to come up with ways to mitigate the
downsides of unbounded polymorphism that you bring up. One idea I've
seen mentioned before is to modify these extension so that they target
a specific instance of IsString/IsList, e.g.:

{-# STRING_LITERALS_AS Text #-}

"foo" ==> (fromString "foo" :: Text)

Another might be more intelligent/powerful defaulting rules, similar
to what we have already with numeric literal overloading.

Michael

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


Re: [Haskell-cafe] Organizaing tests in Haskell

2012-09-23 Thread Jan Stolarek
Thanks for replies. CPP approach seems to be what I would like to achieve, but 
it looks more like 
a hack than a real solution. That said, I like the idea of creating a module 
that acts as an 
external interface to the library and I I don't mind sacrificing encapsulation 
within the package 
itself. If it works for project as big as Yesod it should work for me.

> If you use Hspec[1] for testing, you do not have to assemble your
> individual tests manually into a test suit; hspec-discover[2] takes care
> of that.
I guess that I like to have my tests organized manually. It takes a bit of more 
work and there's a 
risk that I forget to add some test to the suite, but I'm willing to accept 
these drawbacks and 
get more fine-grained control in return.

Jan

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


Re: [Haskell-cafe] Church vs Boehm-Berarducci encoding of Lists

2012-09-23 Thread Kim-Ee Yeoh
On Thu, Sep 20, 2012 at 3:15 PM, wrote:

> Incidentally, there is more than one way to build a predecessor of Church
> numerals. Kleene's solution is not the only one.


Wouldn't you say then that "Church encoding" is still the more appropriate
reference given that Boehm-Berarducci's algorithm is rarely used? And also
that on discovering Church numerals in the untyped setting, one easily sees
how to get it to work in Haskell? Even when one has no inkling of the
larger picture of the embedding into System F?

When I need to encode pattern matching it's goodbye Church and hello Scott.
Aside from your projects, where else is the B-B procedure used?


-- Kim-Ee


On Thu, Sep 20, 2012 at 3:15 PM,  wrote:

>
> Dan Doel wrote:
> > >> P.S. It is actually possible to write zip function using
> Boehm-Berarducci
> > >> encoding:
> > >> http://okmij.org/ftp/Algorithms.html#zip-folds
> >
> > If you do, you might want to consider not using the above method, as I
> > seem to recall it doing an undesirable amount of extra work (repeated
> > O(n) tail).
> It is correct. The Boehm-Berarducci web page discusses at some extent
> the general inefficiency of the encoding, the need for repeated
> reflections and reifications for some (but not all) operations. That
> is why arithmetic on Church numerals is generally a bad idea.
>
> A much better encoding of numerals is what I call P-numerals
> http://okmij.org/ftp/Computation/lambda-calc.html#p-numerals
> It turns out, I have re-discovered them after Michel Parigot (so my
> name P-numerals is actually meaningful). Not only they are faster; one
> can _syntactically_ prove that PRED . SUCC is the identity.
>
> The general idea of course is Goedel's recursor R.
>
>R b a 0 = a
>R b a (Succ n) = b n (R b a n)
>
> which easily generalizes to lists. The enclosed code shows the list
> encoding that has constant-time cons, head, tail and trivially
> expressible fold and zip.
>
>
> Kim-Ee Yeoh wrote:
> > So properly speaking, tail and pred for Church-encoded lists and nats
> > are trial-and-error affairs. But the point is they need not be if we
> > use B-B encoding, which looks _exactly_ the same, except one gets a
> > citation link to a systematic procedure.
> >
> > So it looks like you're trying to set the record straight on who actually
> > did what.
>
> Exactly. Incidentally, there is more than one way to build a
> predecessor of Church numerals. Kleene's solution is not the only
> one. Many years ago I was thinking on this problem and designed a
> different predecessor:
>
> excerpted from http://okmij.org/ftp/Haskell/LC_neg.lhs
>
>
> One ad hoc way of defining a predecessor of a positive numeral
> predp cn+1 ==> cn
> is to represent "predp cn" as "cn f v"
> where f and v are so chosen that (f z) acts as
> if z == v then c0 else (succ z)
> We know that z can be either a numeral cn or a special value v. All
> Church numerals have a property that (cn combI) is combI: the identity
> combinator is a fixpoint of every numeral. Therefore, ((cn combI) (succ
> cn)) reduces to (succ cn). We only need to choose the value v in such
> a way that ((v I) (succ v)) yields c0.
>
> > predp = eval $
> >   c ^ c
> ># (z ^ (z # combI # (succ # z)))   -- function f(z)
> ># (a ^ x ^ c0) -- value v
>
>
> {-# LANGUAGE Rank2Types #-}
>
> -- List represented with R
>
> newtype R x = R{unR :: forall w.
>   -- b
>   (x -> R x -> w -> w)
>   -- a
>   -> w
>   -- result
>   -> w}
>
> nil :: R x
> nil = R (\b a -> a)
>
> -- constant type
> cons :: x -> R x -> R x
> cons x r = R(\b a -> b x r (unR r b a))
>
> -- constant time
> rhead :: R x -> x
> rhead (R fr) = fr (\x _ _ -> x) (error "head of the empty list")
>
> -- constant time
> rtail :: R x -> R x
> rtail (R fr) = fr (\_ r _ -> r) (error "tail of the empty list")
>
> -- fold
> rfold :: (x -> w -> w) -> w -> R x -> w
> rfold f z (R fr) = fr (\x _ w -> f x w) z
>
> -- zip is expressed via fold
> rzipWith :: (x -> y -> z) -> R x -> R y -> R z
> rzipWith f r1 r2 =  rfold f' z r1 r2
>  where f' x tD = \r2 -> cons (f x (rhead r2)) (tD (rtail r2))
>z   = \_  -> nil
>
> -- tests
>
> toR :: [a] -> R a
> toR = foldr cons nil
>
> toL :: R a -> [a]
> toL = rfold (:) []
>
>
> l1 = toR [1..10]
> l2 = toR "abcde"
>
>
> t1 = toL $ rtail l2
> -- "bcde"
>
> t2 = toL $ rzipWith (,) l2 l1
> -- [('a',1),('b',2),('c',3),('d',4),('e',5)]
>
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-23 Thread Roman Cheplyaka
* Heinrich Apfelmus  [2012-09-23 10:51:26+0200]
> Unfortunately, making literals polymorphic does not always achieve
> the desired effect of reducing syntax. In fact, they can instead
> increase syntax! In other words, I would like to point out that there
> is a trade-off involved: is it worth introducing a small syntactic
> reduction at the cost of both a small additional conceptual
> complexity and some syntactic enlargement elsewhere?

Can't you just disable the extension when you realise that it
makes your life harder?

Roman

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


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-23 Thread Chris Smith
Michael Snoyman  wrote:
> That said, it would be great to come up with ways to mitigate the
> downsides of unbounded polymorphism that you bring up. One idea I've
> seen mentioned before is to modify these extension so that they target
> a specific instance of IsString/IsList, e.g.:
>
> {-# STRING_LITERALS_AS Text #-}
>
> "foo" ==> (fromString "foo" :: Text)

That makes sense for OverloadedStrings, but probably not for
OverloadedLists or overloaded numbers... String literals have the
benefit that there's one type that you probably always really meant.
The cases where you really wanted [Char] or ByteString are rare.  On
the other hand, there really is no sensible "I always want this"
answer for lists or numbers.  It seems like a kludge to do it
per-module if each module is going to give different answers most of
the time.

-- 
Chris

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


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-23 Thread Michael Snoyman
On Sun, Sep 23, 2012 at 5:51 PM, Chris Smith  wrote:
> Michael Snoyman  wrote:
>> That said, it would be great to come up with ways to mitigate the
>> downsides of unbounded polymorphism that you bring up. One idea I've
>> seen mentioned before is to modify these extension so that they target
>> a specific instance of IsString/IsList, e.g.:
>>
>> {-# STRING_LITERALS_AS Text #-}
>>
>> "foo" ==> (fromString "foo" :: Text)
>
> That makes sense for OverloadedStrings, but probably not for
> OverloadedLists or overloaded numbers... String literals have the
> benefit that there's one type that you probably always really meant.
> The cases where you really wanted [Char] or ByteString are rare.  On
> the other hand, there really is no sensible "I always want this"
> answer for lists or numbers.  It seems like a kludge to do it
> per-module if each module is going to give different answers most of
> the time.
>
> --
> Chris

Note that I wasn't necessarily advocating such a pragma. And a lot of
my XML code actually *does* use two IsString instances at the same
time, e.g.:

Element ("img" :: Name) (singleton ("href" :: Name) ("foo.png" ::
Text)) [NodeComment ("No content inside an image" :: Text)]

(Courtesy of xml-conduit.)

To prove your point even further, with OverloadedLists we could
replace that `singleton` call with `[("href", "foo.png")]` and then be
using two `IsList` instances simultaneously as well (`Map` and `[]`).

Also, I use the `ByteString` instance of `IsString` regularly when
using `http-conduit` and `warp` (for all of the header values), and to
an even greater extent when hacking on the internals of any HTTP
library (whether `http-conduit` or something in the `wai` ecosystem).

Michael

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


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-23 Thread Brandon Allbery
Maybe what's needed is a way to mutate the lexer by adding new kinds of
literals; Unicode offers a number of paired brackets and quote-like
characters.  Although that is likely to get into readability issues
especially if you do have a mixture of [Char], ByteString, and Text for
some reason.  (Map vs. [] is probably easy enough but add another one or
two in and the sam problem rears its head quickly.)

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Organizaing tests in Haskell

2012-09-23 Thread Heinrich Apfelmus

Simon Hengel wrote:

Of course others are still able to import your Internal modules


That is not necessarily true.  For libraries, you can list internal
modules as other-modules (in contrast to exposed-modules) in you Cabal
file.  That way they are not part of the public interface of your
library.


How do I access internal modules with  cabal test , though? Last time I 
tried, I could not find a way to expose in the test section of the cabal 
file.



Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


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


Re: [Haskell-cafe] Organizaing tests in Haskell

2012-09-23 Thread Simon Hengel
On Sun, Sep 23, 2012 at 06:11:59PM +0200, Heinrich Apfelmus wrote:
> Simon Hengel wrote:
> >>Of course others are still able to import your Internal modules
> >
> >That is not necessarily true.  For libraries, you can list internal
> >modules as other-modules (in contrast to exposed-modules) in you Cabal
> >file.  That way they are not part of the public interface of your
> >library.
> 
> How do I access internal modules with  cabal test , though? Last
> time I tried, I could not find a way to expose in the test section
> of the cabal file.

It works, if you add the source directory to hs-source-dirs of the test
suite (in contrast to depending on the library!), e.g.:

  hs-source-dirs: test, src

or

  hs-source-dirs: test, .

This still has the disadvantage, that the sources are compiled twice.
But I'm not aware of a better way to do it.  If you mostly use GHCi for
development, it's not a big issue.

Cheers,
Simon

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


Re: [Haskell-cafe] Organizaing tests in Haskell

2012-09-23 Thread Simon Hengel
On Sun, Sep 23, 2012 at 04:10:56PM +0200, Jan Stolarek wrote:
> I don't mind sacrificing encapsulation within the package itself. If
> it works for project as big as Yesod it should work for me.

Yesod uses the CPP solution, too (e.g. [1]).

Cheers,
Simon

[1] 
https://github.com/yesodweb/shakespeare/blob/master/shakespeare/Text/Shakespeare.hs

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


[Haskell-cafe] Getting started with Shake

2012-09-23 Thread Richard Wallace
Hey all,

I'm going to be working on a webapp in Haskell in the upcoming months
and am thinking Shake would be a good fit - I'll need to do js, css,
and probably some graphics processing as part of the build and would
like to use Shake to automate deployment.

I'm not entirely sure how to get started with Shake.  I've used to
make, jam, maven, sbt and other build tools in the past.  All of these
keep a build configuration in the project and use that to build the
project.  In sbt, which is most like Shake, the build configuration is
written in Scala and compiled by sbt when you run the build.  The
result of the compilation is saved and reused unless it detects that
the build source files changed.

With shake I'm not sure exactly how to get started.  Should I have a
separate project where I create the build system for the webapp?  Or
can I setup something similar to sbt?

Also, how do I handle dependencies with shake?  cabal will pull in
packages from hackage and do the needful, is there anything in shake
to do the same?  If not, how is it normally done?

Thanks,
Rich

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