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.  Timed Profiling (Ben Rogalski)
   2.  Double vs. Num (Ben Rogalski)
   3. Re:  Timed Profiling (Tim Perry)
   4. Re:  Double vs. Num (Tim Perry)
   5. Re:  Double vs. Num (Christopher Allen)
   6. Re:  Type depending on value (Dmitriy Matrosov)


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

Message: 1
Date: Wed, 4 May 2016 12:11:34 -0400
From: Ben Rogalski <bwrogal...@gmail.com>
To: beginners@haskell.org
Subject: [Haskell-beginners] Timed Profiling
Message-ID:
        <CAL-j+nLfGMJ4ZyEnGTkw5UO-p_HoYL=btonqooc+5oob+sv...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

I would like to generate a time and allocation profiling report after
running my program for exactly 60 seconds (on Ubuntu Linux).

I compiled with the following flags:

-rtsopts -auto-all -caf-all -fforce-recomp

I then ran the program:

The program stops after 60 seconds, but the .prof file is empty.

When I run the program without using timeout, and close it manually (Alt
F4, it is a graphical program), the .prof file contains the information I
would expect.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20160504/abd559fc/attachment-0001.html>

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

Message: 2
Date: Wed, 4 May 2016 18:12:22 -0400
From: Ben Rogalski <bwrogal...@gmail.com>
To: beginners@haskell.org
Subject: [Haskell-beginners] Double vs. Num
Message-ID:
        <CAL-j+n+aAa5nG42+Eti8Lb6t1=km7i=yqdcsacxrujqzdsk...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

I have found that using the type Double in a type signature causes my
program to run much faster than if I use a type variable with a Num
constraint.

Is this common, and if so, why is explicitly using Double faster?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20160504/25816964/attachment-0001.html>

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

Message: 3
Date: Wed, 4 May 2016 16:06:32 -0700
From: Tim Perry <tim.v...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Timed Profiling
Message-ID:
        <cafvgasvegxuce3fpbygwo3ttygy6qo6tysmamv-ztbp7y6s...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

I believe that timeout sends a kill signal to the process in question. I
imagine that the process is killed before the profiling information is
written and so you get an empty file. When you close the program with
alt-F4, the program gets a chance to shut down cleanly and writes on the
profiling information (.prof)


On Wed, May 4, 2016 at 9:11 AM, Ben Rogalski <bwrogal...@gmail.com> wrote:

> I would like to generate a time and allocation profiling report after
> running my program for exactly 60 seconds (on Ubuntu Linux).
>
> I compiled with the following flags:
>
> -rtsopts -auto-all -caf-all -fforce-recomp
>
> I then ran the program:
>
> The program stops after 60 seconds, but the .prof file is empty.
>
> When I run the program without using timeout, and close it manually (Alt
> F4, it is a graphical program), the .prof file contains the information I
> would expect.
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20160504/ed9aa8e9/attachment-0001.html>

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

Message: 4
Date: Wed, 4 May 2016 16:08:41 -0700
From: Tim Perry <tim.v...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Double vs. Num
Message-ID:
        <CAFVgASVDfATE7=c9gydo2ztxk31jq871fw83f8+twv16kre...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

I imagine that in this program when Double isn't specified the compiler
doesn't assign a "hardware optimized" number type. Consequently it isn't
using the specialized functions that are used for 64-bit floating point
numbers. When the program specifies it is receiving the "Double" values,
then it does use the "hardware optimized" data types.

On Wed, May 4, 2016 at 3:12 PM, Ben Rogalski <bwrogal...@gmail.com> wrote:

> I have found that using the type Double in a type signature causes my
> program to run much faster than if I use a type variable with a Num
> constraint.
>
> Is this common, and if so, why is explicitly using Double faster?
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20160504/59684698/attachment-0001.html>

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

Message: 5
Date: Wed, 4 May 2016 18:12:31 -0500
From: Christopher Allen <c...@bitemyapp.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Double vs. Num
Message-ID: <0e49e73b-2cb1-484a-9896-0efca671a...@bitemyapp.com>
Content-Type: text/plain; charset="utf-8"

The default if it?s a Floating type is Double. Leaving the type polymorphic 
breaks sharing, though, and that?s a common cause of perf issues with 
Num/Integral/Floating a => a computations.

Best to post code when asking questions like this.

> On May 4, 2016, at 6:08 PM, Tim Perry <tim.v...@gmail.com> wrote:
> 
> I imagine that in this program when Double isn't specified the compiler 
> doesn't assign a "hardware optimized" number type. Consequently it isn't 
> using the specialized functions that are used for 64-bit floating point 
> numbers. When the program specifies it is receiving the "Double" values, then 
> it does use the "hardware optimized" data types.
> 
> On Wed, May 4, 2016 at 3:12 PM, Ben Rogalski <bwrogal...@gmail.com 
> <mailto:bwrogal...@gmail.com>> wrote:
> I have found that using the type Double in a type signature causes my program 
> to run much faster than if I use a type variable with a Num constraint.
> 
> Is this common, and if so, why is explicitly using Double faster?
> 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org <mailto:Beginners@haskell.org>
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners 
> <http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners>
> 
> 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20160504/0fae17d8/attachment-0001.html>

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

Message: 6
Date: Thu, 5 May 2016 13:14:26 +0300
From: Dmitriy Matrosov <sgf....@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Type depending on value
Message-ID:
        <cafdvufn0kb3kvymnmiv+brh8nohpobfxtahm_d7hws6-tmn...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

> {-# LANGUAGE DataKinds, GADTs, StandaloneDeriving, Rank2Types, PolyKinds, 
> FlexibleInstances, MultiParamTypeClasses, FunctionalDependencies, 
> ScopedTypeVariables #-}

Hi.

Thanks for your answer! There was quite some time passed by, but.. well, i was
trying to figure out how reflection works. I've read [1] (not till the end).
It's a bit too complex for me, but i thought i understand the idea how `reify`
works. But still i can't understand how `reifyNat` works. Here is my code:

> import Unsafe.Coerce
>
> data Nat = Z | S Nat
>   deriving (Show)
>
> data SNat :: Nat -> * where
>     SZ :: SNat 'Z
>     SN :: SNat n -> SNat ('S n)
> deriving instance Show (SNat n)

SNat is a singleton type for Nat. Then i (re-)define `reifyNat`

> data Proxy s = Proxy
>
> class Reifies s a | s -> a where
>   reflect :: p s -> a
>
> class SNatClass (a :: Nat) where
>     singN :: SNat a
>
> instance SNatClass 'Z where
>     singN = SZ
> instance SNatClass n => SNatClass ('S n) where
>     singN = SN singN
>
> fromSNat :: SNat n -> Nat
> fromSNat SZ     = Z
> fromSNat (SN n) = S (fromSNat n)
> {-# NOINLINE fromSNat #-}
>
> instance SNatClass n => Reifies n Nat where
>     reflect _ = fromSNat (singN :: SNat n)
>
> newtype MagicNat r = MagicNat (forall (n :: Nat). SNatClass n => Proxy n -> r)
>
> reifyNat :: forall r. Nat -> (forall (n :: Nat). SNatClass n => Proxy n -> r) 
> -> r
> reifyNat x k = unsafeCoerce (MagicNat k :: MagicNat r) x Proxy
> {-# NOINLINE reifyNat #-}
>
> testNat :: forall (n :: Nat). SNatClass n => Proxy n -> IO ()
> testNat p = case (reflect p) of
>           Z -> print "a"
>           S Z -> print "b"
>           S (S Z) -> print "c"
>           _ -> print "d"
>
> testSNat :: forall (n :: Nat). SNatClass n => Proxy n -> IO ()
> testSNat p = case (singN :: SNat n) of
>           SZ -> print "A"
>           SN SZ -> print "B"
>           SN (SN SZ) -> print "C"
>           _ -> print "D"
>
> main = do
>         print (reifyNat (S (S Z)) reflect)
>         reifyNat (S (S Z)) testNat
>         reifyNat (S (S Z)) testSNat

and now if i dump core:

    ghc-core --no-syntax --no-asm --no-cast -- -dsuppress-var-kinds
    -dsuppress-type-applications -dsuppress-uniques from-snat.hs

i may see, that k takes two arguments: SNatClass dictionary and Proxy

    reifyNat =
      \ (@ r)
        (x :: Nat)
        (k :: forall (n :: Nat).
              SNatClass n =>
              Proxy Nat n -> r) ->
        (k `cast` ...) x (Proxy)

    main7 = S Z
    main6 = S main7

    main5 =
      \ (@ (n :: Nat)) ($dSNatClass :: SNatClass n) _ ->
        fromSNat ($dSNatClass `cast` ...)

    main4 = reifyNat main6 main5

but because SNatClass class has only one method, its dictionary is just a
function `singN` with type `singN :: SNat a`. But if so, why we supply `x ::
Nat` as dictionary in `reifyNat`? Shouldn't we supply value of type `SNat n`?

No need to say, that code above works, and both `testNat` and `testSNat` find
correct instance

*Main> main
S (S Z)
"c"
"C"

but why?

[1]: https://www.schoolofhaskell.com/user/thoughtpolice/using-reflection

On Mon, Apr 11, 2016 at 4:59 PM, Marcin Mrotek
<marcin.jan.mro...@gmail.com> wrote:
> Hello,
>
> In your function, the type `n`, and thus also the value of the
> argument, would have to be known at compile time. I'm not sure if you
> could make it to work. However, you can use the reflection package
> (https://hackage.haskell.org/package/reflection) where you can find a
> `reifyNat` function (
> https://hackage.haskell.org/package/reflection-2.1.2/docs/Data-Reflection.html#g:1
> ) that lets you create a "temporary" type that never escapes the
> callback you give to it, and so it doesn't have to be known at compile
> time:
>
> reifyNat :: forall r. Integer -> (forall n. KnownNat n => Proxy n -> r) -> r
>
> The only requirement is that type `r` doesn't depend in any way on `n`
> (but the computation itself can use it, it just has to return the same
> type every time).
>
> Best regards,
> Marcin Mrotek
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


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

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 5
****************************************

Reply via email to