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.  optimisation of code (PICCA Frederic-Emmanuel)
   2.  Haskell interpretation of names produces error? (trent shipley)
   3. Re:  Haskell interpretation of names produces error?
      (Francesco Ariis)
   4. Re:  optimisation of code (Oleg Nykolyn)
   5. Re:  optimisation of code (David McBride)


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

Message: 1
Date: Fri, 21 Sep 2018 08:25:20 +0000
From: PICCA Frederic-Emmanuel
        <frederic-emmanuel.pi...@synchrotron-soleil.fr>
To: "The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell" <beginners@haskell.org>
Subject: [Haskell-beginners] optimisation of code
Message-ID:
        
<a2a20ec3b8560d408356cac2fc148e53015b32c...@sun-dag3.synchrotron-soleil.fr>
        
Content-Type: text/plain; charset="us-ascii"

Hello,

I would like to have your advice in order to optimize this code.
The purpose is to trigg an action 'a' if a list of files (thousands) exists.
A process copy files from one directory to another.

allFilesThere :: MonadIO m => [Path Abs File] -> m Bool
allFilesThere fs = liftIO $ allM (doesFileExist . fromAbsFile) fs

trigOnAllFiles :: MonadIO m => m r -> [Path Abs File] -> m r
trigOnAllFiles a fs = go
    where
      go = do
        r <- allFilesThere fs
        if r then a else
            ( do liftIO $ threadDelay 1000000
                 go)

It works, but it consums a lot's of resources when all the files does not 
exists yet.
So I would like your advice in order to optimize it :)

thanks for your help.

Frederic


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

Message: 2
Date: Fri, 21 Sep 2018 03:26:02 -0700
From: trent shipley <trent.ship...@gmail.com>
To: beginners@haskell.org
Subject: [Haskell-beginners] Haskell interpretation of names produces
        error?
Message-ID:
        <CAEFLybLneYEhpzkbH2+wi2dMUEHWJXY_0NdOXhyRgh=tc4v...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

data Prop = Const Bool
          | Var Char
          | Not Prop
          | And Prop Prop
          | If Prop Prop
          | Or Prop Prop
          | Yff Prop Prop -- Why do I get errors if "Yff" is replaced with
"Iff"?
          | Xor Prop Prop

type Assoc k v = [(k, v)]

-- Hutton, Graham. Programming in Haskell (p. 93). Cambridge University
Press. Kindle Edition.

find :: Eq k => k -> Assoc k v -> v
find k t = head [v | (k', v) <- t, k == k']

-- Hutton, Graham. Programming in Haskell (p. 93). Cambridge University
Press. Kindle Edition.

type Subst = Assoc Char Bool

-- Hutton, 2016, Ch 8.6

eval :: Subst -> Prop -> Bool
eval _ (Const b) = b
eval s (Var x)   = find x s
eval s (Not p)   = not (eval s p)
eval s (And p q) = eval s p && eval s q
eval s (If p q)  = eval s p <= eval s q
eval s (Or p q)  = eval s p || eval s q
eval s (Yff p q) = eval s p == eval s q  -- Iff produces error here
eval s (Xor p q) = eval s p /= eval s q

-- Hutton 2016 Ch 8.6

vars :: Prop -> [Char]
vars (Const _)  = []
vars (Var x)    = [x]
vars (Not p)    = vars p
vars (And p q)  = vars p ++ vars q
vars (If p q)   = vars p ++ vars q
vars (Or p q)   = vars p ++ vars q
vars (Yff p q)  = vars p ++ vars q -- Iff produces error here
vars (Xor p q)  = vars p ++ vars q

-- Hutton 2016 Ch 8.6
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20180921/b91846f9/attachment-0001.html>

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

Message: 3
Date: Fri, 21 Sep 2018 12:42:23 +0200
From: Francesco Ariis <fa...@ariis.it>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] Haskell interpretation of names
        produces error?
Message-ID: <20180921104223.aqjkxwzsvj76b...@x60s.casa>
Content-Type: text/plain; charset=us-ascii

Hello trent,

On Fri, Sep 21, 2018 at 03:26:02AM -0700, trent shipley wrote:
> data Prop = Const Bool
> [...]

changing all the three occurrences of Yff to Iff does not produce
error.
If you change only two you will get an error, because you have a
pattern-matching against a non-existent constructor
-F


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

Message: 4
Date: Fri, 21 Sep 2018 13:46:16 +0300
From: Oleg Nykolyn <jurav...@gmail.com>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] optimisation of code
Message-ID:
        <CALqbk1Rq0pMwH6ArBSheqiCidnk8M=mo8qriyhkqygnofib...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi,

Current code re-checks file existence always in same order, so worst case
is - N files and only last of them does not exists.
In that case this code will re-check (N-1) files during each consecutive
retry.
This can be optimized by moving already existing files to the end of file
list(or dropping them from list completely, if files are only added but
never removed).
For this you could re-write `allFilesThere` something like:
allFilesThere fs = liftIO $ do
  existing, non_existing <- partitionM (doesFileExist . fromAbsFile) fs
  return (non_existing++ existing, null non_existing)

Then allFilesThere could start next iteration by checking previously
non-existing files and probably failing much faster.

On Fri, Sep 21, 2018 at 11:25 AM PICCA Frederic-Emmanuel <
frederic-emmanuel.pi...@synchrotron-soleil.fr> wrote:

> Hello,
>
> I would like to have your advice in order to optimize this code.
> The purpose is to trigg an action 'a' if a list of files (thousands)
> exists.
> A process copy files from one directory to another.
>
> allFilesThere :: MonadIO m => [Path Abs File] -> m Bool
> allFilesThere fs = liftIO $ allM (doesFileExist . fromAbsFile) fs
>
> trigOnAllFiles :: MonadIO m => m r -> [Path Abs File] -> m r
> trigOnAllFiles a fs = go
>     where
>       go = do
>         r <- allFilesThere fs
>         if r then a else
>             ( do liftIO $ threadDelay 1000000
>                  go)
>
> It works, but it consums a lot's of resources when all the files does not
> exists yet.
> So I would like your advice in order to optimize it :)
>
> thanks for your help.
>
> Frederic
> _______________________________________________
> 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/20180921/3b361ecc/attachment-0001.html>

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

Message: 5
Date: Fri, 21 Sep 2018 07:45:46 -0400
From: David McBride <toa...@gmail.com>
To: Haskell Beginners <beginners@haskell.org>
Subject: Re: [Haskell-beginners] optimisation of code
Message-ID:
        <CAN+Tr41sPwqnVvLa3XAxRHgi=KoY63skus=4ctdmvof1jus...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

My first instinct is to just use anyM instead of allM

allFilesThere :: MonadIO m => [Path Abs File] -> m Bool
allFilesThere fs = liftIO $ anyM (not . doesFileExist . fromAbsFile) fs

However you'll now have the opposite problem.  It will take a lot of
resources when all the files are there.  But maybe that is okay for your
use case?

On Fri, Sep 21, 2018 at 4:25 AM PICCA Frederic-Emmanuel <
frederic-emmanuel.pi...@synchrotron-soleil.fr> wrote:

> Hello,
>
> I would like to have your advice in order to optimize this code.
> The purpose is to trigg an action 'a' if a list of files (thousands)
> exists.
> A process copy files from one directory to another.
>
> allFilesThere :: MonadIO m => [Path Abs File] -> m Bool
> allFilesThere fs = liftIO $ allM (doesFileExist . fromAbsFile) fs
>
> trigOnAllFiles :: MonadIO m => m r -> [Path Abs File] -> m r
> trigOnAllFiles a fs = go
>     where
>       go = do
>         r <- allFilesThere fs
>         if r then a else
>             ( do liftIO $ threadDelay 1000000
>                  go)
>
> It works, but it consums a lot's of resources when all the files does not
> exists yet.
> So I would like your advice in order to optimize it :)
>
> thanks for your help.
>
> Frederic
> _______________________________________________
> 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/20180921/4fc93550/attachment.html>

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

Subject: Digest Footer

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


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

End of Beginners Digest, Vol 123, Issue 9
*****************************************

Reply via email to