[Haskell-cafe] why GHC cannot infer type in this case?

2013-02-01 Thread oleg

Dmitry Kulagin wrote:
 I try to implement little typed DSL with functions, but there is a problem:
 compiler is unable to infer type for my functions. 

One way to avoid the problem is to start with the tagless final
representation. It imposes fewer requirements on the type system, and
is a quite mechanical way of embedding DSL. The enclosed code
re-implements your example in the tagless final style. If later you
must have a GADT representation, one can easily write an interpreter
that interprets your terms as GADTs (this is mechanical). For more
examples, see the (relatively recent) lecture notes

http://okmij.org/ftp/tagless-final/course/lecture.pdf

{-# LANGUAGE TypeOperators, KindSignatures, DataKinds #-}
{-# LANGUAGE NoMonomorphismRestriction, TypeFamilies #-}
module TestExp where

-- types of DSL terms
data Ty = Int16 | TFun [Ty] Ty | TSeq [Ty]

-- DSL terms
class Exp (repr :: Ty - *) where
int16:: Int - repr Int16
add  :: repr Int16 - repr Int16 - repr Int16 

decl :: (repr (TSeq ts) - repr t) - repr (TFun ts t)
call :: repr (TFun ts t) - repr (TSeq ts) - repr t

-- building and deconstructing sequences
unit :: repr (TSeq '[])
cons :: repr t - repr (TSeq ts) - repr (TSeq (t ': ts))
deco :: (repr t - repr (TSeq ts) - repr w) - repr (TSeq (t ': ts))
- repr w

-- A few convenience functions
deun :: repr (TSeq '[]) - repr w - repr w
deun _ x = x

singleton :: Exp repr = (repr t - repr w) - repr (TSeq '[t]) - repr w
singleton body = deco (\x _ - body x)

-- sample terms
fun =  decl $ singleton (\x - add (int16 2) x)
-- Inferred type
-- fun :: Exp repr = repr (TFun ((:) Ty 'Int16 ([] Ty)) 'Int16)

test = call fun (cons (int16 3) unit)
-- Inferred type
-- test :: Exp repr = repr 'Int16

fun2 =  decl $ deco (\x - singleton (\y - add (int16 2) (add x y)))
{- inferred 
fun2
  :: Exp repr =
 repr (TFun ((:) Ty 'Int16 ((:) Ty 'Int16 ([] Ty))) 'Int16)
-}

test2 = call fun2 (int16 3 `cons` (int16 4 `cons` unit))



-- Simple evaluator

-- Interpret the object type Ty as Haskell type *
type family TInterp (t :: Ty) :: *
type instance TInterp Int16 = Int
type instance TInterp (TFun ts t) = TISeq ts - TInterp t
type instance TInterp (TSeq ts)   = TISeq ts

type family TISeq (t :: [Ty]) :: *
type instance TISeq '[]   = ()
type instance TISeq (t1 ': ts) = (TInterp t1, TISeq ts)

newtype R t = R{unR:: TInterp t}

instance Exp R where
int16 = R
add (R x) (R y) = R $ x + y

decl f = R $ \args - unR . f . R $ args
call (R f) (R args) = R $ f args

unit = R ()
cons (R x) (R y) = R (x,y)
deco f (R (x,y)) = f (R x) (R y)


testv = unR test
-- 5

tes2tv = unR test2
-- 9



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


Re: [Haskell-cafe] Yet another Conduit question

2013-02-01 Thread Simon Marechal
On 01/02/2013 08:21, Michael Snoyman wrote:
 So you're saying you want to keep the same grouping that you had
 originally? Or do you want to batch up a certain number of results?
 There are lots of ways of approaching this problem, and the types don't
 imply nearly enough to determine what you're hoping to achieve here.

Sorry for not being clear. I would like to group them as much as
possible, that is up to a certain limit, and also within a time
threshold. I believe that the conduit code will be called only when
something happens in the conduit, so an actual timer would be useless
(unless I handle this at the source perhaps, and propagate ticks).

That is why in my first message I talked about stacking things into the
list until the conduit has no more input available, or a maximum size is
reached, but was not sure this even made sense.

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


Re: [Haskell-cafe] Ticking time bomb

2013-02-01 Thread Alexander Kjeldaas
Forgot the list.


On Fri, Feb 1, 2013 at 10:21 AM, Alexander Kjeldaas 
alexander.kjeld...@gmail.com wrote:


 Trying to avoid the wrath of Ketil I'll refrain from suggesting to do
 anything, I'll just explain why git is good at this, and not arbitrary. :-)

 Most systems that I know of to verify *anything*, use merkle trees, or
 something very similar.
 http://en.wikipedia.org/wiki/Hash_tree

 For example the TPM chip on your motherboard, used for example to ensure
 the integrity of the Google Chromebook and Windows BitLocker
 http://en.wikipedia.org/wiki/Trusted_Platform_Module
 (simplified example: in secure memory it stores H1=hash(microcode), then
 H2=hash(H1 || BIOS), then H3=hash(H2 || MBR), then H4=hash(H3 || kernel),
 ...).

 Or the integrity of the bitcoin currency.
 https://en.bitcoin.it/wiki/Protocol_specification#Merkle_Trees

 So these are pretty different systems, but it all boils down to doing
 cryptographic secure hashes over a previous hash + new data to ensure
 integrity of the new combined data.  Given only one verified hash in such a
 system, no part of the data, nor its history of mutation can be forged.
  History can mean which software runs on your computer (TPM), which
 transactions are valid (Bitcoin), or which commits have been done in a SCM
 (git, mercurial).

 So git is not magical, it is just a practical implementation of something
 that works.  Any other *general* solution will be based on similar basic
 principles.  Mercurial does this and there is a GPG extension for it.

 Bazaar does not use a SHA1-based content addressable storage, so while a
 signed commit signs the tree, it does not represent the history (no hash
 of hash, only hash if you look at it as a merkle tree), but it does
 chain commits. To verify a tree + history, *all* commits must be signed,
 which is fragile IMO.

 Regarding Darcs, my understanding is that it deliberately rejects hashing
 the tree, so it is not clear to me how to verify tree+history.  Patches can
 be signed, but as long as patches are independent, there is no hash of
 hash component which makes it difficult to see how one can verify the
 tree.  My understanding of darcs is very limited though.

 But to be *practical* the rest of the workflow should be secure as well,
 so you need:

 1. A way to distribute the merkle tree (git pull/clone/push).
 Distribution is of the data that is to be signed is required for
 security, because otherwise the representation of the data itself (web view
 or 'git diff') can be compromised.  Signatures have no meaning if you
 cannot trust that you know what you sign.
 2. A way to sign a change to the merkle tre (git commit -S, git tag -s etc)
 3. A way to have multiple signatures on a given hash (i.e. commit, or tag,
 or whatever it is called in a particular merkle tree implementation).
 This is required to avoid catastrophic owning of core developers.
  If required, I do think that multiple signatures can be emulated by a
 structured set of commits that have single signatures though.
 3. A way to reliably do code reviews on the changes to the data (git diff)
 This is really the same as 1).  We cannot reliably do 'git diff'
 unless the developers do it on their own equipment, thus the system must be
 distributed.
 4. Given the requirement for a distributed merkle tree, some merge
 strategy is needed.  It is thus practical, though not required, to have
 good support for this.
 (Btw, even the bitcoin hash chain has a merge strategy - the tree with
 the most compute power will win, and others are forced to rebase their
 transactions on that tree)


 So my choice of git is not arbitrary.  The way git works is pretty
 fundamental to verifying the integrity of stuff.

 Though when I have looked through the other options, mercurial might be a
 better fit since it is supported on Windows.

 Trying to solve this problem from scratch might not be such a good idea,
 because it might be very close to a reimplementation of git or mercurial.
  Or maybe it is a good idea for someone who has some time on their hands.
  Just be aware that the requirements for verifying anything is very close
 to what existing distributed SCM systems do.

 Alexander


 On Fri, Feb 1, 2013 at 3:32 AM, Kevin Quick qu...@sparq.org wrote:

 Git has the ability to solve all of this.

 ...

  2. Uploads to hackage either happen through commits to the git
 repository,
 or an old-style upload to hackage automatically creates a new anonymous
 branch in the git repository.
 3. The git repository is authorative.  Signing releases, code reviews
 etc.
 all happens through the git repositories.  This gives us all the
 flexibility of a git-style trust model.

 ...

  5. Who owns which package names can be held in a separate meta-tree git
 repository, and can have consensus requirements on commits.
 6. This special meta-tree can also contain suggested verification keys
 for
 commits to the other hackage git trees.  It can even contain keys that
 

Re: [Haskell-cafe] linking errors while compile hugs98 in macos

2013-02-01 Thread Junior White
Thanks! With your help, I have compiled hugs on my macbook! I'll try to
embed it into my game client engine next week.


On Fri, Feb 1, 2013 at 1:19 PM, Brandon Allbery allber...@gmail.com wrote:

 On Thu, Jan 31, 2013 at 10:15 PM, Junior White efi...@gmail.com wrote:

 So that lua best fits the rule very well, but i like haskell much more.
 After doing some research, I find in the haskell world, there is a hugs
 fits my  demands. I'm sad to know that no one is maintaining hugs any more.
 I asking someone to keep develop on it, if no one, can I do it myself?


 Probably you could, but the effort needed might be significant.  In
 particular fixing things like environ see
 https://bugs.ruby-lang.org/attachments/2591/ruby-changes.patch for the
 kind of change you'll need to make, although I have to say the way they
 chose to do it is risky at best (but sadly typical).  Probably something
 similar for other missing symbols; feel free to ask me for help in private
 email.

 --
 brandon s allbery kf8nh   sine nomine
 associates
 allber...@gmail.com
 ballb...@sinenomine.net
 unix, openafs, kerberos, infrastructure, xmonad
 http://sinenomine.net

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


[Haskell-cafe] Optimizing performance problems with Aeson rendering large Text arrays

2013-02-01 Thread Oliver Charles

Hello,

In summary, i'm working on an application that responds to a users query, a
sequence index, with the union of a list of UUIDs that have changed 
since that
same sequence index, split into 6 sections. I wish to respond to these 
queries
via JSON to provide an easy to use web service, and for the most part, 
what I

have works.

The problem I am having is that profiling seems to show that the 
majority of the

time spent in my application is encoding this to JSON, and also that the
application is only 60% productive with 40% allocations happening in
Data.Aeson.encode (and friends).

Here's an overview of what I'm doing, the full code can be found at the 
end of

this email.

I am storing my data in memory as an IntMap, from sequence index to a 
changeset:



IntMap ChangeSet


Where a ChangeSet is essentially a tuple of HashSet's of UUIDs:


data ChangeSet = ChangeSet { artistChanges :: !(HashSet MBID)
   , labelChanges :: !(HashSet MBID)
   , recordingChanges :: !(HashSet MBID)
   , releaseChanges :: !(HashSet MBID)
   , releaseGroupChanges :: !(HashSet MBID)
   , workChanges :: !(HashSet MBID)
   }
  deriving (Generic)


The MBID newtype is just a newtype around Text, but you can only create 
MBIDs by
parsing a UUID fromString - just to enforce a bit more correctness, but 
without

the cost of having to serialize the UUID to JSON.

When I query, I splitLookup on the IntMap to get the requested change set by
sequence index, and all future changesets. I union all of these, and 
then render

the response back to the client:


let (_, !cs, !futureCs) = IntMap.splitLookup csId changeSets
writeLBS $ encode $ mconcat $
  catMaybes $ map Just (IntMap.elems futureCs) ++ [ cs ]


None of this shows up in profiling however, and here's what I see:


Thu Jan 31 17:03 2013 Time and Allocation Profiling Report  (Final)

   Main +RTS -p -RTS

total time  =4.75 secs   (4748 ticks @ 1000 us, 1 processor)
total alloc = 4,329,582,160 bytes  (excludes profiling overheads)

COST CENTRE MODULE %time %alloc

encode  Data.Aeson.Encode   23.5 17.4
string  Data.Aeson.Encode   18.5 35.1
break   Data.Aeson.Encode   17.5 2.3
mconcat Main15.1 9.7
fromValue/Array Data.Aeson.Encode9.2 14.8
toJSON  Main 5.7 9.0
send.loop   Snap.Internal.Http.Server.HttpPort   3.0 0.0
mapIter Snap.Iteratee2.1 2.3
parseJSON   Main 1.7 3.0
writeLBSSnap.Internal.Types  1.1 4.9

COST CENTRE MODULEno. entries  %time 
%alloc   %time %alloc


MAINMAIN 21600.00.0   100.0  100.0
 main   Main 43300.00.0   100.0  100.0
  main.sinceMain 106310.00.075.3   78.7
   encode   Data.Aeson.Encode 13910   23.5   
17.475.3   78.7
fromValue/ObjectData.Aeson.Encode1395 2540.0
0.046.0   52.2
 fromValue/ArrayData.Aeson.Encode1420 7577.9   
12.036.4   25.7
  fromValue/String  Data.Aeson.Encode1422 30890950.7
0.028.5   13.7
   string   Data.Aeson.Encode1423 3089095   10.2   
11.427.8   13.7
break   Data.Aeson.Encode1425 3089095   17.5
2.317.52.3
 string Data.Aeson.Encode1396 8848.3   
23.7 9.6   26.6
  fromValue/Array   Data.Aeson.Encode 142101.3
2.9 1.32.9
   fromValue/String Data.Aeson.Encode 142400.0
0.0 0.00.0
  break Data.Aeson.Encode1397 8840.0
0.0 0.00.0
toJSON  Main 1393 1275.7
9.0 5.79.0



Unless I'm reading this incorrectly, this shows that 75% of the time is 
spent in

encode, along with almost 80% of my allocations. While the performance of my
application is actually satisfactory (I respond in around 0.04s), I'd 
still like
to do better - if only for the practical experience of learning how to 
optimize.


Any ideas what I can do about this? I feel like I might get better 
performance
if fromValue/Array new that I had a vector of Text values, and they 
could just
be intercalated with ,  - but I have no idea how the internals of Text 
works

so this might really perform the same as the fold that is currently used.

I am compiling for benchmarking purposes with:


ghc -Wall -fno-warn-orphans -Werror -O2 -rtsopts \
  -hide-package hashable-1.2.0.5 Main.hs


And I 

Re: [Haskell-cafe] Why does not zipWith' exist

2013-02-01 Thread Andres Löh
Hi Kazu.

I'd be surprised if zipWith' yields significant improvements. In the
case of foldl', the strictness affects an internal value (the
accumulator). However, in the case of zipWith', you're just forcing
the result a bit more, but I guess the normal use pattern of fibs is
that you want to see a prefix of the result anyway. So the overall
amount of evaluation is the same.

I've tried to hack up a quick criterion test comparing my own naive
zipWith, the Prelude zipWith (which may have additional optimizations,
I haven't checked), and zipWith':

import Criterion.Main
import Prelude hiding (zipWith)
import qualified Prelude as P

zipWith :: (a - b - c) - [a] - [b] - [c]
zipWith f (a:as) (b:bs) = f a b : zipWith f as bs
zipWith _ _  _  = []

zipWith' :: (a - b - c) - [a] - [b] - [c]
zipWith' f (a:as) (b:bs) = x `seq` x : zipWith' f as bs
  where
x = f a b
zipWith' _ _ _ = []

fibs :: () - [Integer]
fibs () = go
  where
go :: [Integer]
go = 0 : 1 : zipWith (+) go (tail go)

fibsP :: () - [Integer]
fibsP () = go
  where
go :: [Integer]
go = 0 : 1 : P.zipWith (+) go (tail go)

fibs' :: () - [Integer]
fibs' () = go
  where
go :: [Integer]
go = 0 : 1 : zipWith' (+) go (tail go)

main :: IO ()
main = defaultMain $ [
bench fibs  (nf (take 1 . fibs ) ())
  , bench fibsP (nf (take 1 . fibsP) ())
  , bench fibs' (nf (take 1 . fibs') ())
  ]

The additional () arguments are to prevent GHC from sharing the list
in between calls. I haven't tested thoroughly if GHC looks through
this hack and optimizes it anyway.

Compiling without optimization, I get 1.15ms/1.11ms/1.10ms.
With -O, I get 85us/85us/88us.

Am I overlooking anything? What's your test?

Cheers,
  Andres

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


Re: [Haskell-cafe] Why does not zipWith' exist

2013-02-01 Thread Daniel Fischer
On Friday 01 February 2013, 12:50:18, Andres Löh wrote:
 Hi Kazu.
 
 I'd be surprised if zipWith' yields significant improvements. In the
 case of foldl', the strictness affects an internal value (the
 accumulator). However, in the case of zipWith', you're just forcing
 the result a bit more, but I guess the normal use pattern of fibs is
 that you want to see a prefix of the result anyway. So the overall
 amount of evaluation is the same.
 
 I've tried to hack up a quick criterion test comparing my own naive
 zipWith, the Prelude zipWith (which may have additional optimizations,
 I haven't checked), and zipWith':

 
 main :: IO ()
 main = defaultMain $ [
 bench fibs  (nf (take 1 . fibs ) ())
   , bench fibsP (nf (take 1 . fibsP) ())
   , bench fibs' (nf (take 1 . fibs') ())
   ]
 
 The additional () arguments are to prevent GHC from sharing the list
 in between calls. I haven't tested thoroughly if GHC looks through
 this hack and optimizes it anyway.
 
 Compiling without optimization, I get 1.15ms/1.11ms/1.10ms.
 With -O, I get 85us/85us/88us.
 
 Am I overlooking anything? What's your test?

zipWith' would [I haven't tested, but I'm rather confident] make a difference 
if 
you benchmarked

bench name (whnf (fibs !!) 10)

etc.

The reason is that 

foo = initialValues : zipWith f foo (tail foo)

is rather a scan than a real zip, so evaluating an element depends on 
evaluating all previous elements, and thus can build a huge thunk if the 
elements aren't demanded in order.

For a real zip where an element of the result does not depend on the values of 
earlier elements, plain zipWith would perform (usually only marginally) better 
than zipWith'.

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


Re: [Haskell-cafe] Ticking time bomb

2013-02-01 Thread Christopher Done
Hey dude, it looks like we made the same project yesterday:

http://www.reddit.com/r/haskell/comments/17njda/proposal_a_trivial_cabal_package_signing_utility/

Yours is nice as it doesn't depend on GPG. Although that could be a
nice thing because GPG manages keys. Dunno.

Another diff is that mine puts the .sig inside the .tar.gz, yours puts
it separate.

=)

On 31 January 2013 09:11, Vincent Hanquez t...@snarc.org wrote:
 On 01/30/2013 07:27 PM, Edward Z. Yang wrote:

 https://status.heroku.com/incidents/489

 Unsigned Hackage packages are a ticking time bomb.

 I agree this is terrible, I've started working on this, but this is quite a
 bit of work and other priorities always pop up.

 https://github.com/vincenthz/cabal
 https://github.com/vincenthz/cabal-signature

 My current implementation generate a manifest during sdist'ing in cabal, and
 have cabal-signature called by cabal on the manifest to create a
 manifest.sign.

 The main issue i'm facing is how to create a Web of Trust for doing all the
 public verification bits.

 --
 Vincent


 ___
 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] Optimizing performance problems with Aeson rendering large Text arrays

2013-02-01 Thread Oliver Charles
Urgh, the formatting got totally destroyed in sending, I think. If so, 
here's a paste of my email as I intended it to be sent:


http://hpaste.org/81648

Sorry about that!
- Ocharles

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


Re: [Haskell-cafe] Why does not zipWith' exist

2013-02-01 Thread Daniel Fischer
On Friday 01 February 2013, 13:06:09, Daniel Fischer wrote:
 
 zipWith' would [I haven't tested, but I'm rather confident] make a
 difference if you benchmarked
 
 bench name (whnf (fibs !!) 10)
 
 etc.

Well, it took a little bit of persuasion to let GHC not cache the list(s), but 
with


fibs :: Int - Integer
fibs k = igo i !! k
  where
i | k  100 = 1
  | otherwise   = 2
igo :: Integer - [Integer]
igo i = let go = 0 : i : zipWith (+) go (tail go) in go

etc., benchmarking

main :: IO ()
main = defaultMain $ [
bench fibs  (whnf fibs 2)
  , bench fibsP (whnf fibsP 2)
  , bench fibs' (whnf fibs' 2)
  ]

shows a clear difference:

benchmarking fibs 
mean: 14.50178 ms, lb 14.27410 ms, ub 14.78909 ms, ci 0.950
benchmarking fibsP
mean: 13.69060 ms, lb 13.59516 ms, ub 13.81583 ms, ci 0.950
benchmarking fibs'
mean: 3.155886 ms, lb 3.137776 ms, ub 3.177367 ms, ci 0.950


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


Re: [Haskell-cafe] Why does not zipWith' exist

2013-02-01 Thread Andres Löh
 Well, it took a little bit of persuasion to let GHC not cache the list(s), but
 with


 fibs :: Int - Integer
 fibs k = igo i !! k
   where
 i | k  100 = 1
   | otherwise   = 2
 igo :: Integer - [Integer]
 igo i = let go = 0 : i : zipWith (+) go (tail go) in go

 etc., benchmarking

 main :: IO ()
 main = defaultMain $ [
 bench fibs  (whnf fibs 2)
   , bench fibsP (whnf fibsP 2)
   , bench fibs' (whnf fibs' 2)
   ]

 shows a clear difference:

 benchmarking fibs
 mean: 14.50178 ms, lb 14.27410 ms, ub 14.78909 ms, ci 0.950
 benchmarking fibsP
 mean: 13.69060 ms, lb 13.59516 ms, ub 13.81583 ms, ci 0.950
 benchmarking fibs'
 mean: 3.155886 ms, lb 3.137776 ms, ub 3.177367 ms, ci 0.950

Right, I'm not arguing that it's impossible to produce a difference,
but I think that if you're defining the sequence of fibs, the most
likely scenario might be that you're actually interested in a prefix,
and more importantly, you can still, from the outside, force the
prefix even if you're only interested in a particular element. The
second point, imho, is what makes zipWith inherently different from a
function such as foldl'. You can equivalently define zipWith' as a
wrapper around zipWith:

zipWith' :: (a - b - c) - [a] - [b] - [c]
zipWith' f xs ys = strictify (zipWith f xs ys)
  where
strictify :: [a] - [a]
strictify []   = []
strictify (x : xs) = x `seq` x : strictify xs

You cannot easily do the same for foldl and foldl'.

Cheers,
  Andres

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


Re: [Haskell-cafe] Why does not zipWith' exist

2013-02-01 Thread Daniel Fischer
On Friday 01 February 2013, 13:43:59, Andres Löh wrote:
 
 Right, I'm not arguing that it's impossible to produce a difference,
 but I think that if you're defining the sequence of fibs, the most
 likely scenario might be that you're actually interested in a prefix,

Right. If you only want one Fibonacci number with a not too small index, you 
should use a dedicated algorithm.

I was just providing a possible answer to

 Am I overlooking anything? What's your test?

to show how the desire for zipWith' might arise from the fibs example.

 and more importantly, you can still, from the outside, force the
 prefix even if you're only interested in a particular element. The
 second point, imho, is what makes zipWith inherently different from a
 function such as foldl'.

Right, and as I said in my first post, the fibs example is more of a scan than 
a 
zip. And for scans it's natural to consume the list in order [if you only want 
one element, a fold is the proper function].

 You can equivalently define zipWith' as a
 wrapper around zipWith:
 
 zipWith' :: (a - b - c) - [a] - [b] - [c]
 zipWith' f xs ys = strictify (zipWith f xs ys)
   where
 strictify :: [a] - [a]
 strictify []   = []
 strictify (x : xs) = x `seq` x : strictify xs
 
 You cannot easily do the same for foldl and foldl'.

I don't even see how one could do it non-easily.

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


Re: [Haskell-cafe] Ticking time bomb

2013-02-01 Thread Vincent Hanquez
On Fri, Feb 01, 2013 at 01:07:33PM +0100, Christopher Done wrote:
 Hey dude, it looks like we made the same project yesterday:
 
 http://www.reddit.com/r/haskell/comments/17njda/proposal_a_trivial_cabal_package_signing_utility/
 
 Yours is nice as it doesn't depend on GPG. Although that could be a
 nice thing because GPG manages keys. Dunno.
 
 Another diff is that mine puts the .sig inside the .tar.gz, yours puts
 it separate.

Nice to see a productive discussion on this. /me really need to read reddit 
more :)

Couple of details, no the signature is going inside the tarball too.  the
signature process happens during the sdisting after building the manifest.  My
reason for doing is, which i suspect similar to yours, is that I don't need to
modify hackage this way and the uploading stays the same. Also in my case,
cabal-signature is called by cabal, not by the user. I can't see this effort
working without forcing everyone to use it (transparently in the background)

For gpg, i don't know what's the right answer. One on hand it's solving all
the problems related to this already, but on the other portability issue.

I was thinking maybe one way to verify the key that i use for signing,
would be to tie it to a personal gpg key (by signing the key with a gpg key) to
benefit from all the facilities that gpg provides. It would provide a cheap way
to switch model later, without being tied to a gpg signing process.

-- 
Vincent

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


Re: [Haskell-cafe] Optimizing performance problems with Aeson rendering large Text arrays

2013-02-01 Thread Bas van Dijk
On Feb 1, 2013 1:15 PM, Oliver Charles ol...@ocharles.org.uk wrote:

 Urgh, the formatting got totally destroyed in sending, I think. If so,
here's a paste of my email as I intended it to be sent:

 http://hpaste.org/81648

 Sorry about that!
 - Ocharles


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

If I make a special case for text based UUIDs in aeson:

data Value = ... | UUID Text | ...

Data.Aeson.Encode.fromValue (UUID s) = singleton ''  fromText s 
singleton ''

Then encoding time improves by 20%.

So a big part of the time is spent encoding the UUID strings.

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


Re: [Haskell-cafe] Most used functions in hackage

2013-02-01 Thread Rustom Mody
On Tue, Jan 29, 2013 at 1:53 PM, Casey Basichis caseybasic...@gmail.comwrote:

 Hi Dmitry,

 Thanks for the links.  I've been through the 24 Days of Hackage, but I
 think its time to run through them again now that I'm a little more
 familiar with everything.

 Why do you think browsing function by function is a bad idea?  It seems
 that knowing exactly what the most used functions are would be an extremely
 effective way of finding both which parts of the Prelude and Hackage are
 most broadly useful (instead of browsing them like a phonebook) and also
 finding support from the community as the most commonly used functions
 would likely be the easiest to find support for.


Find out the most used functions seems to be eminently desirable.
To do that we need to count function-uses.
And to do that we need to know what to count.

Do we?

If you remember, the cost-centre mode of counting functions in haskell
programs was precisely because the usual (first-order language) mode of
counting would lead to the strange conclusion that map and foldr were the
most used and therefore most inefficient functions in Haskell! So a new way
of counting had to be devised.

There is a book: Mathsemantics by Edward Macneal which deals with things
like:
How does an airline count the number of passengers. I quote from the book:

I 1980 I was one passenger, ten passengers, eighteen passengers, thirty-six
 passengers, forty-two passengers, fifty-five passengers, seventy-two
 passengers and ninety-four passengers.  Each of these statements is true.


He then goes on to explain.

I was one passenger in the sense that I was a person who traveled by air in
 that year.
 I was eighteen passengers in the sense that I made eighteen round trips.
 I was forty-two passengers in the sense that on forty-two different
 occasions I entered and exited the system of a different carrier.
 I was seventy-two passengers in the sense that on seventy-two occasions I
 was on board an aircraft when it took off from one place and landed at
 another.
 I was ninety-four passengers in the sense that I made ninety-four separate
 entrances and exits from airport terminal buildings.


[He missed the explanation for 10!]

He goes on to say that these differences are not mere technicalities and
its important to get the sense of 'passenger'

So… like 'passenger', how many meanings does 'function-use' have?

Rusi
-- 
http://www.the-magus.in
http://blog.languager.org
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] linking errors while compile hugs98 in macos

2013-02-01 Thread Rustom Mody
On Fri, Feb 1, 2013 at 8:45 AM, Junior White efi...@gmail.com wrote:

 Sadly! I like hugs because it can embed in my game client as lua. For game
 logic language, I think the following properties are important:
 1. Portable, works on pc,macosx,ios,android even flash or web.
 2. Intepret, for quick develop, quick test.
 3. Hot code load, for online bugfix.
 4. Small, game client need to be as small as possiable

 So that lua best fits the rule very well, but i like haskell much more.
 After doing some research, I find in the haskell world, there is a hugs
 fits my  demands. I'm sad to know that no one is maintaining hugs any more.
 I asking someone to keep develop on it, if no one, can I do it myself?



I used gofer (predecessor of hugs) to teach programming in the early 90s.
Some changes which I made to it are here
https://github.com/rusimody/gofer
It did compile a few months ago with gcc 4.7

Rusi
-- 
http://www.the-magus.in
http://blog.languager.org
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does not zipWith' exist

2013-02-01 Thread Niklas Hambüchen
I recently asked a similar question about strict scans (e.g. scanl') 
and got the same response to use a strictify function.

Although I would argue that fun' is syntactically more convenient than 
(strictList . fun), I'd agree that composition is good.

Maybe it would make sense to add to have that strictList function in 
Data.List instead?

On Fri 01 Feb 2013 13:19:08 GMT, Daniel Fischer wrote:
 On Friday 01 February 2013, 13:43:59, Andres Löh wrote:

 

  Right, I'm not arguing that it's impossible to produce a difference,

  but I think that if you're defining the sequence of fibs, the most

  likely scenario might be that you're actually interested in a prefix,



 Right. If you only want one Fibonacci number with a not too small
 index, you should use a dedicated algorithm.



 I was just providing a possible answer to



  Am I overlooking anything? What's your test?



 to show how the desire for zipWith' might arise from the fibs example.



  and more importantly, you can still, from the outside, force the

  prefix even if you're only interested in a particular element. The

  second point, imho, is what makes zipWith inherently different from a

  function such as foldl'.



 Right, and as I said in my first post, the fibs example is more of a
 scan than a zip. And for scans it's natural to consume the list in
 order [if you only want one element, a fold is the proper function].



  You can equivalently define zipWith' as a

  wrapper around zipWith:

 

  zipWith' :: (a - b - c) - [a] - [b] - [c]

  zipWith' f xs ys = strictify (zipWith f xs ys)

  where

  strictify :: [a] - [a]

  strictify [] = []

  strictify (x : xs) = x `seq` x : strictify xs

 

  You cannot easily do the same for foldl and foldl'.



 I don't even see how one could do it non-easily.



 Cheers,

 Daniel



 ___
 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] Most used functions in hackage

2013-02-01 Thread Casey Basichis
That book Mathsemantics sounds like something I should read, would you
recommend it?

Your point occurred to me the other day when measuring number of downloads
of whole packages was mentioned as being the ideal measure.

I have more confidence in measuring the contents of the packages themselves
as creating a Hackage package suggests a competency with the language and
baseline of sophistication.

My thought was the best measure might be the count of functions across all
packages, where an included function in any individual package would only
be counted once per package.

In this sense, map and fold would still likely be towards the top, but that
is as it should be.

But it seems there are many measures that would be useful, like the
percentage of functions from a package that tend to get used in the same
project - do people nit pick particular functions from a specific package
or does the package use tend to require the use of all of its functions in
every project the package is used in.

I'd love to hear some thoughts on this as I generally don't know where to
begin in solving these sorts of problems and would like to know more about
those methods in general.

Casey


On Fri, Feb 1, 2013 at 7:00 AM, Rustom Mody rustompm...@gmail.com wrote:

 On Tue, Jan 29, 2013 at 1:53 PM, Casey Basichis 
 caseybasic...@gmail.comwrote:

 Hi Dmitry,

 Thanks for the links.  I've been through the 24 Days of Hackage, but I
 think its time to run through them again now that I'm a little more
 familiar with everything.

 Why do you think browsing function by function is a bad idea?  It seems
 that knowing exactly what the most used functions are would be an extremely
 effective way of finding both which parts of the Prelude and Hackage are
 most broadly useful (instead of browsing them like a phonebook) and also
 finding support from the community as the most commonly used functions
 would likely be the easiest to find support for.


 Find out the most used functions seems to be eminently desirable.
 To do that we need to count function-uses.
 And to do that we need to know what to count.

 Do we?

 If you remember, the cost-centre mode of counting functions in haskell
 programs was precisely because the usual (first-order language) mode of
 counting would lead to the strange conclusion that map and foldr were the
 most used and therefore most inefficient functions in Haskell! So a new way
 of counting had to be devised.

 There is a book: Mathsemantics by Edward Macneal which deals with things
 like:
 How does an airline count the number of passengers. I quote from the book:

 I 1980 I was one passenger, ten passengers, eighteen passengers,
 thirty-six passengers, forty-two passengers, fifty-five passengers,
 seventy-two passengers and ninety-four passengers.  Each of these
 statements is true.


 He then goes on to explain.

 I was one passenger in the sense that I was a person who traveled by air
 in that year.
 I was eighteen passengers in the sense that I made eighteen round trips.
 I was forty-two passengers in the sense that on forty-two different
 occasions I entered and exited the system of a different carrier.
 I was seventy-two passengers in the sense that on seventy-two occasions I
 was on board an aircraft when it took off from one place and landed at
 another.
 I was ninety-four passengers in the sense that I made ninety-four
 separate entrances and exits from airport terminal buildings.


 [He missed the explanation for 10!]

 He goes on to say that these differences are not mere technicalities and
 its important to get the sense of 'passenger'

 So… like 'passenger', how many meanings does 'function-use' have?

 Rusi
 --
 http://www.the-magus.in
 http://blog.languager.org




-- 
Casey James Basichis
Composer - Cartoon Network
http://www.caseyjamesbasichis.com
caseybasic...@gmail.com
310.387.7540
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Most used functions in hackage

2013-02-01 Thread Gwern Branwen
One thing you could do is download Hackage (easy enough with a little
scripting of 'cabal list'; see for example
http://www.haskell.org/pipermail/haskell-cafe/2011-July/093669.html ),
unpack, and use Language.Haskell.Exts to parse every Haskell file.
Here are two examples from the past:

1. http://www.haskell.org/pipermail/haskell-cafe/2012-January/098618.html
function-name search script which lets you parse a large number of
source files and print out anything calling a specified function (eg.
if you were thinking about deprecating something)
2. http://www.haskell.org/pipermail/haskell-cafe/2011-May/091663.html
language-extension search script; I used it to see how many source
files ever invoked LANGUAGE pragmas and which ones.

-- 
gwern
http://www.gwern.net

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


Re: [Haskell-cafe] Most used functions in hackage

2013-02-01 Thread Rustom Mody
On Fri, Feb 1, 2013 at 9:41 PM, Casey Basichis caseybasic...@gmail.comwrote:

 That book Mathsemantics sounds like something I should read, would you
 recommend it?



Well its quite a favourite of mine, if that counts as a recommendation…



 Your point occurred to me the other day when measuring number of downloads
 of whole packages was mentioned as being the ideal measure.

 I have more confidence in measuring the contents of the packages
 themselves as creating a Hackage package suggests a competency with the
 language and baseline of sophistication.

 My thought was the best measure might be the count of functions across all
 packages, where an included function in any individual package would only
 be counted once per package.

 In this sense, map and fold would still likely be towards the top, but
 that is as it should be.

 But it seems there are many measures that would be useful, like the
 percentage of functions from a package that tend to get used in the same
 project - do people nit pick particular functions from a specific package
 or does the package use tend to require the use of all of its functions in
 every project the package is used in.

 I'd love to hear some thoughts on this as I generally don't know where to
 begin in solving these sorts of problems and would like to know more about
 those methods in general.


Well… it seems to be a good idea to back off from here a bit and ask how we
came here.
You want to learn haskell  for which you want to pinpoint the 'most' used
functions.
Lets leave aside the question that 'most' may be harder to specify than we
may first imagine.

Instead lets make a map (functor?) from learning the programming language
Haskell to learning the natural language English.
So I dont know English (and yeah there are Godelian anomalies in that
statement) and I gather that vocabulary is a key to mastering the language.
Now Webster is a bit too fat to cram up as a whole so I decide to isolate
the 5000 most used English words.
Do you think my English mastery will be improved that way?
Surely Webster had a bigger vocabulary than Shakespeare.
Do you think Webster knew English better than Shakespeare?
[You can of course replace Shakespeare to whoever happens to take your
fancy]

IOW mastering the paradigm is more important than the details.

Now its important to get that the paradigm cannot be caught in any
single-point sloganeering such as:
Functional programming is programming without side-effects
Haskell is syntactically sugared lambda calculus
The key feature of Haskell is its sexy type magic

Nevertheless its also true that 'paradigm' consists of far fewer elements
than 'the 500 most used functions.'

I have a couple of pages on my blog:
http://blog.languager.org/2012/10/functional-programming-lost-booty.html
gives a few of the basics that FPers should know (IMHO) before going to
advanced stuff. I should mention that it was written it because Haskell is
becoming increasingly hard for beginners with the focus on 'type-magic' is
overshadowing the basics. [In any case after 25 years of teaching, I am
finding it harder and harder to teach] If you have crossed over the basic
stage it may not be much use to you :-)

There is also
http://blog.languager.org/2011/02/cs-education-is-fat-and-weak-1.html and
sequel
which is more of a grumble about CS education than about FP/Haskell per se.
Still, an undercurrent of that grumble is that much of the nonsense of CS
education is because FP has not become mainstream soon enough.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Optimizing performance problems with Aeson rendering large Text arrays

2013-02-01 Thread Oliver Charles

On 02/01/2013 01:44 PM, Bas van Dijk wrote:


If I make a special case for text based UUIDs in aeson:

data Value = ... | UUID Text | ...

Data.Aeson.Encode.fromValue (UUID s) = singleton ''  fromText s  
singleton ''


Then encoding time improves by 20%.

So a big part of the time is spent encoding the UUID strings.

Bas

This might work, but it doesn't seem to be something I could actually 
distribute, unless I shipped modified Aeson source code... the String 
fromValue pattern seems to do a lot of escaping which won't apply to my 
UUIDs, but I'm not sure what the right solution to that is.


- Ocharles

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


Re: [Haskell-cafe] Most used functions in hackage

2013-02-01 Thread Casey Basichis
I just ordered Mathsemantics for a hefty $2.10.

Your article's were an enjoyable read and very informative.  I'll dig more
into you blog tonight.

I've read the Great Good book, Haskell school of music, and I'm working my
way through Real World Haskell. I've also read countless blog articles on
Haskell.

With a great deal read and understood about Haskell I have no confidence
that I can make anything in it at all.

Kurt Vonnegut retyped James Joyce's work to feel a great novel under his
fingers before writing his own.

Webster knew English better than Shakespeare.  Shakespeare was a master of
creation.

To be able to create from a small core and then extend those intuitions
with knowledge over time is to me far more effective than mastering
language and then attempting creation.

While not rigorous, getting hands on with high level practical libraries
and working by example would have built my intuitions far faster than all
of the countless reading and toy examples I've done.  The problem is, for
that approach, there isn't any material for a book or insightful blog post
to be written. Mimetics are mundane and unnecessary to those in the know.
 The teachers seem to be unaware of how their own intuitions were formed.

While learning the fundamentals my mind struggles to imagine how these
basic concepts play into the larger picture - how would they use foldr to
build persistent?  I don't have real answers to those questions but it's a
constant distraction.

I am certain that sitting down with a few simple examples of how to use a
library like Persistent, without any concern as to how it works, will
surely take me from a useless Haskeller to being able to make useful tools
that I can use in my career as a composer.

In learning Do notation the books took me through three ways of expressing
the same thing before arriving at the sugary syntax that I will likely use
for the next ten projects. I don't see that as building a core towards
creation, but rather the elevation of a fetishy obsession with language.
 Children learn the most critical words before grammar - only in language
studies does grammar come before vocabulary.

The question is what is the core knowledge that facilitates creation?

That core is a mutating form.  It works from the high level downward as it
needs to, not from the low level upward because it is thought that it
should.  There are thousands of articles on how to use raw C++ pointers.
One in the know knows to use smart pointers because they facilitate
creation.

I constantly read authors of blog posts say things like I wish I had
learned monad transformers sooner.  What is a rigorous way to prioritize
learning the full scope of Haskell so that creative intuition is maximized?
 How can I know that Arrows will be generally more effective than
Category-Extras for creating things?

If data mining Hackage to find the practical reality of how Haskell is
actually being used by people who are creating complete and useful things
is not an effective way to learn, what approach is better?

Best,
Casey


On Fri, Feb 1, 2013 at 10:05 AM, Rustom Mody rustompm...@gmail.com wrote:



 On Fri, Feb 1, 2013 at 9:41 PM, Casey Basichis caseybasic...@gmail.comwrote:

 That book Mathsemantics sounds like something I should read, would you
 recommend it?



 Well its quite a favourite of mine, if that counts as a recommendation…



 Your point occurred to me the other day when measuring number of
 downloads of whole packages was mentioned as being the ideal measure.

 I have more confidence in measuring the contents of the packages
 themselves as creating a Hackage package suggests a competency with the
 language and baseline of sophistication.

 My thought was the best measure might be the count of functions across
 all packages, where an included function in any individual package would
 only be counted once per package.

 In this sense, map and fold would still likely be towards the top, but
 that is as it should be.

 But it seems there are many measures that would be useful, like the
 percentage of functions from a package that tend to get used in the same
 project - do people nit pick particular functions from a specific package
 or does the package use tend to require the use of all of its functions in
 every project the package is used in.

 I'd love to hear some thoughts on this as I generally don't know where to
 begin in solving these sorts of problems and would like to know more about
 those methods in general.


 Well… it seems to be a good idea to back off from here a bit and ask how
 we came here.
 You want to learn haskell  for which you want to pinpoint the 'most' used
 functions.
 Lets leave aside the question that 'most' may be harder to specify than we
 may first imagine.

 Instead lets make a map (functor?) from learning the programming language
 Haskell to learning the natural language English.
 So I dont know English (and yeah there are Godelian anomalies in that
 statement) and I gather 

Re: [Haskell-cafe] Why does not zipWith' exist

2013-02-01 Thread 山本和彦
Hi,

 zipWith' would [I haven't tested, but I'm rather confident] make a difference 
 if 
 you benchmarked
 
 bench name (whnf (fibs !!) 10)
 
 etc.

Yes. fibs is slow if used with !!.

--Kazu

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


Re: [Haskell-cafe] Why does not zipWith' exist

2013-02-01 Thread 山本和彦
 Right, I'm not arguing that it's impossible to produce a difference,
 but I think that if you're defining the sequence of fibs, the most
 likely scenario might be that you're actually interested in a prefix,
 and more importantly, you can still, from the outside, force the
 prefix even if you're only interested in a particular element. 

Three topics are repeatedly discussed among beginners in Japan:

1) fibs implemented with zipWith
2) simple quicksort
3) sieve of eratosthenes

Some people use 1) with !! and say it's slow, why?.

Some people say 2) is not a true quicksort because it is not in-place.

Some people say 3) is not the sieve of eratosthenes at all because,
for example, 7 is divided by 5.

These three examples are mis-leading. In my opinion, if we use them,
we should

- use them as is, but describe such opinions OR
- use better implementations

I don't know translations work well but you can find such discussions
here:

http://d.hatena.ne.jp/kazu-yamamoto/20100624
http://d.hatena.ne.jp/nishiohirokazu/20100622/1277208908
http://d.hatena.ne.jp/mkotha/20100623/1277286946

--Kazu

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


Re: [Haskell-cafe] linking errors while compile hugs98 in macos

2013-02-01 Thread Junior White
Thanks. I will have a try.


On Fri, Feb 1, 2013 at 11:15 PM, Rustom Mody rustompm...@gmail.com wrote:

 On Fri, Feb 1, 2013 at 8:45 AM, Junior White efi...@gmail.com wrote:

 Sadly! I like hugs because it can embed in my game client as lua. For
 game logic language, I think the following properties are important:
 1. Portable, works on pc,macosx,ios,android even flash or web.
 2. Intepret, for quick develop, quick test.
 3. Hot code load, for online bugfix.
 4. Small, game client need to be as small as possiable

 So that lua best fits the rule very well, but i like haskell much more.
 After doing some research, I find in the haskell world, there is a hugs
 fits my  demands. I'm sad to know that no one is maintaining hugs any more.
 I asking someone to keep develop on it, if no one, can I do it myself?



 I used gofer (predecessor of hugs) to teach programming in the early 90s.
 Some changes which I made to it are here
 https://github.com/rusimody/gofer
 It did compile a few months ago with gcc 4.7

 Rusi
 --
 http://www.the-magus.in
 http://blog.languager.org


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


Re: [Haskell-cafe] Most used functions in hackage

2013-02-01 Thread Rustom Mody
On Sat, Feb 2, 2013 at 3:38 AM, Casey Basichis caseybasic...@gmail.comwrote:

 I just ordered Mathsemantics for a hefty $2.10.

 Your article's were an enjoyable read and very informative.  I'll dig more
 into you blog tonight.

 I've read the Great Good book, Haskell school of music, and I'm working my
 way through Real World Haskell. I've also read countless blog articles on
 Haskell.

 With a great deal read and understood about Haskell I have no confidence
 that I can make anything in it at all.

 Kurt Vonnegut retyped James Joyce's work to feel a great novel under his
 fingers before writing his own.

 Webster knew English better than Shakespeare.  Shakespeare was a master
 of creation.

 To be able to create from a small core and then extend those intuitions
 with knowledge over time is to me far more effective than mastering
 language and then attempting creation.

 While not rigorous, getting hands on with high level practical libraries
 and working by example would have built my intuitions far faster than all
 of the countless reading and toy examples I've done.  The problem is, for
 that approach, there isn't any material for a book or insightful blog post
 to be written. Mimetics are mundane and unnecessary to those in the know.
  The teachers seem to be unaware of how their own intuitions were formed.

 While learning the fundamentals my mind struggles to imagine how these
 basic concepts play into the larger picture - how would they use foldr to
 build persistent?  I don't have real answers to those questions but it's a
 constant distraction.

 I am certain that sitting down with a few simple examples of how to use a
 library like Persistent, without any concern as to how it works, will
 surely take me from a useless Haskeller to being able to make useful tools
 that I can use in my career as a composer.

 In learning Do notation the books took me through three ways of expressing
 the same thing before arriving at the sugary syntax that I will likely use
 for the next ten projects. I don't see that as building a core towards
 creation, but rather the elevation of a fetishy obsession with language.
  Children learn the most critical words before grammar - only in language
 studies does grammar come before vocabulary.

 The question is what is the core knowledge that facilitates creation?

 That core is a mutating form.  It works from the high level downward as it
 needs to, not from the low level upward because it is thought that it
 should.  There are thousands of articles on how to use raw C++ pointers.
 One in the know knows to use smart pointers because they facilitate
 creation.

 I constantly read authors of blog posts say things like I wish I had
 learned monad transformers sooner.  What is a rigorous way to prioritize
 learning the full scope of Haskell so that creative intuition is maximized?
  How can I know that Arrows will be generally more effective than
 Category-Extras for creating things?

 If data mining Hackage to find the practical reality of how Haskell is
 actually being used by people who are creating complete and useful things
 is not an effective way to learn, what approach is better?

 Best,
 Casey


Lets say you teach the piano and two prospective students come to you.
A with much passion wants to play like this
http://www.youtube.com/watch?v=3L0Rncqx1yQ
B with more focus than passion, has this ideal
http://www.youtube.com/watch?v=Yu06WnXlPCY

Who do you think/feel would be more likely to succeed?
Who would you prefer to teach?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Most used functions in hackage

2013-02-01 Thread Casey Basichis
I'm not sure what you mean.

I would imagine popular success for either would be circumstantial and have
little to do with their actual ability and more to do with the
opportunities they pursue and the cultural atmosphere at the time.

For this student:
http://www.youtube.com/watch?v=_bjKDJD-CLc
I would have a very clear idea of the many things I would excise from the
typical piano education to help her form her musical intuitions as simply
and effectively as possible, with the knowledge that in time, she will find
her own way to a personal style and repertoire.

You are being a little cryptic.  I don't see how the nuances that
differentiate two experts relates.


On Fri, Feb 1, 2013 at 10:31 PM, Rustom Mody rustompm...@gmail.com wrote:



 On Sat, Feb 2, 2013 at 3:38 AM, Casey Basichis caseybasic...@gmail.comwrote:

 I just ordered Mathsemantics for a hefty $2.10.

 Your article's were an enjoyable read and very informative.  I'll dig
 more into you blog tonight.

 I've read the Great Good book, Haskell school of music, and I'm working
 my way through Real World Haskell. I've also read countless blog articles
 on Haskell.

 With a great deal read and understood about Haskell I have no confidence
 that I can make anything in it at all.

 Kurt Vonnegut retyped James Joyce's work to feel a great novel under his
 fingers before writing his own.

 Webster knew English better than Shakespeare.  Shakespeare was a master
 of creation.

 To be able to create from a small core and then extend those intuitions
 with knowledge over time is to me far more effective than mastering
 language and then attempting creation.

 While not rigorous, getting hands on with high level practical libraries
 and working by example would have built my intuitions far faster than all
 of the countless reading and toy examples I've done.  The problem is, for
 that approach, there isn't any material for a book or insightful blog post
 to be written. Mimetics are mundane and unnecessary to those in the know.
  The teachers seem to be unaware of how their own intuitions were formed.

 While learning the fundamentals my mind struggles to imagine how these
 basic concepts play into the larger picture - how would they use foldr to
 build persistent?  I don't have real answers to those questions but it's a
 constant distraction.

 I am certain that sitting down with a few simple examples of how to use a
 library like Persistent, without any concern as to how it works, will
 surely take me from a useless Haskeller to being able to make useful tools
 that I can use in my career as a composer.

 In learning Do notation the books took me through three ways of
 expressing the same thing before arriving at the sugary syntax that I will
 likely use for the next ten projects. I don't see that as building a core
 towards creation, but rather the elevation of a fetishy obsession with
 language.  Children learn the most critical words before grammar - only in
 language studies does grammar come before vocabulary.

 The question is what is the core knowledge that facilitates creation?

 That core is a mutating form.  It works from the high level downward as
 it needs to, not from the low level upward because it is thought that it
 should.  There are thousands of articles on how to use raw C++ pointers.
 One in the know knows to use smart pointers because they facilitate
 creation.

 I constantly read authors of blog posts say things like I wish I had
 learned monad transformers sooner.  What is a rigorous way to prioritize
 learning the full scope of Haskell so that creative intuition is maximized?
  How can I know that Arrows will be generally more effective than
 Category-Extras for creating things?

 If data mining Hackage to find the practical reality of how Haskell is
 actually being used by people who are creating complete and useful things
 is not an effective way to learn, what approach is better?

 Best,
 Casey


 Lets say you teach the piano and two prospective students come to you.
 A with much passion wants to play like this
 http://www.youtube.com/watch?v=3L0Rncqx1yQ
 B with more focus than passion, has this ideal
 http://www.youtube.com/watch?v=Yu06WnXlPCY

 Who do you think/feel would be more likely to succeed?
 Who would you prefer to teach?




-- 
Casey James Basichis
Composer - Cartoon Network
http://www.caseyjamesbasichis.com
caseybasic...@gmail.com
310.387.7540
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe