Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  audio generation (Anton Felix Lorenzen)
   2. Re:  audio generation (Daniel Bergey)
   3. Re:  Trying to prove Applicative is superclass    of Functor,
      etc (Silent Leaf)
   4. Re:  Trying to prove Applicative is       superclass      of Functor,
      etc (Daniel Bergey)
   5. Re:  audio generation (Dennis Raddle)
   6. Re:  audio generation (Daniel Bergey)


----------------------------------------------------------------------

Message: 1
Date: Sat, 30 Apr 2016 14:18:20 +0200
From: Anton Felix Lorenzen <anfe...@posteo.de>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] audio generation
Message-ID: <5724a28c.9090...@posteo.de>
Content-Type: text/plain; charset=windows-1252; format=flowed

AFAIK, graphic card programming is usually done with accelerate.
Packages that depend on accelerate can be found here:

http://packdeps.haskellers.com/reverse/accelerate


------------------------------

Message: 2
Date: Sat, 30 Apr 2016 14:00:11 -0400
From: Daniel Bergey <ber...@alum.mit.edu>
To: Dennis Raddle <dennis.rad...@gmail.com>, Haskell Beginners
        <beginners@haskell.org>
Subject: Re: [Haskell-beginners] audio generation
Message-ID:
        <878tzvrn84.fsf@chladni.i-did-not-set--mail-host-address--so-tickle-me>
        
Content-Type: text/plain; charset=utf-8

The entire topic of space use in Haskell is not simple, but the part you
need here may be.  As long as GHC can tell that values already written
to disk may be garbage collected, memory use is quite reasonable.

For example, here's a short program that prints a long-ish list:

xs :: [Double]
xs = map cos [1..1e7]

main :: IO ()
main = traverse_ print $ map sin xs

It runs in constant space, of less than 1 MB.  (I ran it on a few
smaller cases to confirm that max residency stays the same order of
magnitude.)  Note the difference between "bytes allocated" and "total
memory in use".

$ ./laziness +RTS -sstderr  > /dev/null
 181,493,398,808 bytes allocated in the heap
     414,623,400 bytes copied during GC
         131,736 bytes maximum residency (2 sample(s))
          23,520 bytes maximum slop
               1 MB total memory in use (0 MB lost due to fragmentation)

This next program generates random numbers.  You could use the State
monad; here I've just used the infinite list generator in System.Random.

main = do
  g <- newStdGen
  let xs = take 100000 (randoms g) :: [Int]
  traverse_ print xs

This one also runs in constant space:

$ ./.cabal-sandbox/bin/lazyRandom +RTS -sstderr > /dev/null
     380,128,240 bytes allocated in the heap
         238,472 bytes copied during GC
          44,312 bytes maximum residency (2 sample(s))
          21,224 bytes maximum slop
               1 MB total memory in use (0 MB lost due to fragmentation)

Based on these tests, I'd recommend trying to structure your program as
a map or fold over a (lazy) list.  If that structure makes sense for your
problem, I'd expect managing memory usage to be as simple as the cases
above.  I expect that memory usage will be constant in the number of
samples, although higher than my examples because each sample is bigger
than the Int or Double I used.

Let me know if you want me to elaborate on any of this.

bergey

On 2016-04-29 at 23:58, Dennis Raddle <dennis.rad...@gmail.com> wrote:
> I'm writing a program that will use functions to generate audio. The Haskell 
> code will
> write the audio samples to disk---no need for real time playback. I see some 
> useful
> libraries for writing audio files.?
>
> My question concerns efficiency when generating several million to 20 million 
> samples
> (or even many times more than that if I use high-resolution sampling rates). 
> They can be
> generated one at a time in sequence, so there's no need to occupy a lot of 
> memory or
> postpone thunk evaluation. I'm going to need efficient disk writing. Note 
> that I may
> need some pseudorandom numbers in my calculations, so I might want to 
> calculate samples
> by state monadic computations to carry the generator state. What is my 
> general strategy
> going to be for memory and time efficiency? I am pretty confused by Haskell 
> "strictness"
> and normal head form and all that, which often doesn't seem to be very 
> strict. Or bang
> patterns, etc. Is it going to be simple to understand what I need??
>
> Dennis
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


------------------------------

Message: 3
Date: Sat, 30 Apr 2016 21:14:03 +0200
From: Silent Leaf <silent.le...@gmail.com>
To: D?niel Arat? <exitcons...@gmail.com>, The Haskell-Beginners
        Mailing List - Discussion of primarily beginner-level topics related
        to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Trying to prove Applicative is
        superclass      of Functor, etc
Message-ID:
        <cagfccjnfnrzd70jxcf9l7ff7gay3zattumpmtc6xr0o1gdy...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

I think I got what exactly was the change of ghc 7.10. basically it only
adds a constraint Applicative on the Monad class, and same with
Functor/Applicative. it doesn't automatically write implied instances, but
just forces one to actually write said instances of those superclasses. In
short you can't anymore make monads without making Applicatives,
"beforehand" (even though order is not important).

In my opinion it's pretty shitty. I totally agree that it's (partially)
more mathematically correct, and that's great. yet in my opinion, given
superclasses can always be derived from their subclasses, it should be
mathematically automatic to prove superclass instances by proving any
subclass thereof. Otherwise it's forcing the programmer to do even more
possibly-useless work (we don't always need applicative and functors for
every use of a new monad, do we?) without gaining anything in return but a
very abstract idea of "correctness". in short i think if they wanted
mathematical correctness they should have added automatic instanciation of
superclasses, with possibility to override the default definitions, like
they do so with some superfluous methods.

Not that write functors or applicative functor instances is actually
heavywork, of course, thankfully.

I kinda wonder, can we define Applicative methods in function of Monad
methods, even though those latter can only be type-valid if the Applicative
instance is already created and checked? or maybe we can write a
class-neutral version (without constraints)?
Say something like that:
> -------- version one, with constraints
> mkAp :: (Monad m, Applicative m) => m (a -> b) -> m a -> m b
> mkAp mf ma = mf >>= \f -> ma >>= \a -> return $ f a
> -- (not entirely sure on the necessary constraints of this type
signature...)
> instance Functor f => Applicative f where
>   <*> = mkAp
>      -- the value is automatically different depending on the instance
right?
>   pure = return

course, I'm pretty sure mkAp == ap, aka the monad equivalent of (<*>) is
automatically defined at instanciation of the monad. But i think to
remember it uses fmap, and in theory the idea is that neither instances of
Functor or Applicative would yet exist. All depends on the possibility to
define a superclass instance in terms of a subclass instance.

> -------- version two, without class -- can we use type constructors in
signature without classes?
> mkAp :: (**signature of bind**) -> (a -> m a) -> (( m (a -> b) -> m a ->
m b  ))
> mkAp bind return mf ma = ... -- defined in terms of those given
class-independent functions

I'mma check myself but if it fails i wonder if anyone knows a way around?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20160430/769fd1dc/attachment-0001.html>

------------------------------

Message: 4
Date: Sat, 30 Apr 2016 17:18:44 -0400
From: Daniel Bergey <ber...@alum.mit.edu>
To: Silent Leaf <silent.le...@gmail.com>, D?niel Arat?
        <exitcons...@gmail.com>, The Haskell-Beginners Mailing List -
        Discussion of primarily beginner-level topics related to Haskell
        <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Trying to prove Applicative is
        superclass      of Functor, etc
Message-ID:
        <8760uyssln.fsf@chladni.i-did-not-set--mail-host-address--so-tickle-me>
        
Content-Type: text/plain

On 2016-04-30 at 15:14, Silent Leaf <silent.le...@gmail.com> wrote:
> I think I got what exactly was the change of ghc 7.10. basically it only adds 
> a
> constraint Applicative on the Monad class, and same with
> Functor/Applicative.

7.10 adds the constraint on the Monad class.  Prior to 7.10, both Monads
and Applicatives already needed to be Functors.

> Otherwise it's forcing the programmer to do even more possibly-useless
> work (we don't always need applicative and functors for every use of a
> new monad, do we?)

The practical advantage comes when I want to write some code that is
generic over Monads.  If I can't assume that every Monad is Applicative,
my choices are:

1) Write (Applicative m, Monad m) =>, and not work for those Monads
2) Write `ap` everywhere I mean <*>, which for some instances is less
efficient
3) Write two versions, one like (1) and one like (2)

None of these are very appealing, and orphan instances are a pain, so
there's already strong social pressure that any Monad instance on
Hackage should have the corresponding Applicative instance defined.

> in short i think if they wanted mathematical correctness they should
> have added automatic instanciation of superclasses, with possibility
> to override the default definitions, like they do so with some
> superfluous methods.

Several ways of automatically defining superclasses were discussed as
part of the AMP changes.  Maybe we'll get one in some future GHC.  I
don't know the details, but some of the discussion:

https://ghc.haskell.org/trac/ghc/wiki/IntrinsicSuperclasses
https://ghc.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances
https://ghc.haskell.org/trac/ghc/wiki/InstanceTemplates

> Not that write functors or applicative functor instances is actually 
> heavywork, of
> course, thankfully.

You know that if the instances are all in the same module, you can use
the Monad functions, right?  So the extra work is just pasting in:

 instance Functor m where
    fmap = liftM
 
instance Applicative m where
    pure  = return
    (<*>) = ap


------------------------------

Message: 5
Date: Sat, 30 Apr 2016 17:16:41 -0700
From: Dennis Raddle <dennis.rad...@gmail.com>
To: Haskell Beginners <beginners@haskell.org>
Subject: Re: [Haskell-beginners] audio generation
Message-ID:
        <cakxlvorifwte-dvk7++boe0a6koczww7mz2hdp0pfwsnrhk...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

On Sat, Apr 30, 2016 at 11:00 AM, Daniel Bergey <ber...@alum.mit.edu> wrote:

> The entire topic of space use in Haskell is not simple, but the part you
> need here may be.  As long as GHC can tell that values already written
> to disk may be garbage collected, memory use is quite reasonable.
>
> For example, here's a short program that prints a long-ish list:
>
> xs :: [Double]
> xs = map cos [1..1e7]
>
> main :: IO ()
> main = traverse_ print $ map sin xs
>
>


Thanks. I'll see if this works for me. My question right now is, what is
traverse_print? Is that the same as

main = traverse print . map sin $ xs

?

I'm guessing IO is traversable and for some reason you don't want to use
mapM.

D
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20160430/cbd9762c/attachment-0001.html>

------------------------------

Message: 6
Date: Sat, 30 Apr 2016 22:08:50 -0400
From: Daniel Bergey <ber...@alum.mit.edu>
To: Dennis Raddle <dennis.rad...@gmail.com>, Haskell Beginners
        <beginners@haskell.org>
Subject: Re: [Haskell-beginners] audio generation
Message-ID:
        <8737q2sf65.fsf@chladni.i-did-not-set--mail-host-address--so-tickle-me>
        
Content-Type: text/plain

On 2016-04-30 at 20:16, Dennis Raddle <dennis.rad...@gmail.com> wrote:
>     main :: IO ()
>     main = traverse_ print $ map sin xs
>
> Thanks. I'll see if this works for me. My question right now is, what is 
> traverse_print?
> Is that the same as
>
> main = traverse print . map sin $ xs
>
> ?
>
> I'm guessing IO is traversable and for some reason you don't want to use mapM.

traverse_ is in Data.Foldable [1]

You're right that it's closely related to `traverse` and `mapM`.  I
generally prefer `traverse` and `traverse_` to `mapM` and `mapM_`
because they only require Applicative, not Monad.  So they work in more
cases, and generic code can be more generic.

The versions with the _ give back `f ()` instead of `f b` - in this
case, we get `IO ()` instead of `IO [()]`.  If you try with `traverse,
the program won't typecheck, because main needs to have type `IO ()`.

bergey

Footnotes: 
[1]  
http://hackage.haskell.org/package/base-4.8.2.0/docs/Data-Foldable.html#v:traverse_



------------------------------

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


------------------------------

End of Beginners Digest, Vol 95, Issue 1
****************************************

Reply via email to