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.  Could not deduce (Frame a r0) arising from a     use of `len'
      (PICCA Frederic-Emmanuel)
   2.  short-circuit like Maybe monad with a difference (Dennis Raddle)
   3. Re:  short-circuit like Maybe monad with a        difference
      (Imants Cekusins)
   4. Re:  short-circuit like Maybe monad with a        difference
      (Dennis Raddle)
   5. Re:  short-circuit like Maybe monad with a        difference
      (Imants Cekusins)
   6. Re:  short-circuit like Maybe monad with a        difference
      (Dennis Raddle)
   7.  Just wanted to share some GHCI macros with       fellow beginners
      (Lai Boon Hui)


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

Message: 1
Date: Fri, 30 Sep 2016 14:18:14 +0000
From: PICCA Frederic-Emmanuel
        <frederic-emmanuel.pi...@synchrotron-soleil.fr>
To: "Beginners@haskell.org" <Beginners@haskell.org>
Subject: [Haskell-beginners] Could not deduce (Frame a r0) arising
        from a  use of `len'
Message-ID:
        
<a2a20ec3b8560d408356cac2fc148e53bb2e0...@sun-dag3.synchrotron-soleil.fr>
        
Content-Type: text/plain; charset="us-ascii"

Hello I try to write something like this

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}

module Hkl.Frame
       ( Frame(..)
       , frames
       , frames'
       ) where

import Pipes
import Control.Monad

class (Frame a r) where
  len :: a -> IO (Maybe Int)
  row :: a -> Int -> IO r

frames :: (Frame a r) => Pipe a r IO ()
frames = do
  d <- await
  (Just n) <- lift $ len d
  forM_ [0..n-1] (\i' -> do
                     f <- lift $ row d i'
                     yield f)


But when I try to compile this I get this error message.


    Could not deduce (Frame a r0) arising from a use of `len'
    from the context (Frame a r)
      bound by the type signature for
                 frames :: Frame a r => Pipe a r IO ()
      at src/Hkl/Frame.hs:17:11-39
    The type variable `r0' is ambiguous
    Possible fix: add a type signature that fixes these type variable(s)
    In the second argument of `($)', namely `len d'
    In a stmt of a 'do' block: (Just n) <- lift $ len d
    In the expression:
      do { d <- await;
           (Just n) <- lift $ len d;
           forM_
             [0 .. n - 1]
             (\ i'
                -> do { f <- lift $ row d i';
                        .... }) }


What should I do in order to solve this problem.

Thanks


Frederic

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

Message: 2
Date: Fri, 30 Sep 2016 13:28:03 -0700
From: Dennis Raddle <dennis.rad...@gmail.com>
To: Haskell Beginners <beginners@haskell.org>
Subject: [Haskell-beginners] short-circuit like Maybe monad with a
        difference
Message-ID:
        <CAKxLvopjuFJg5KLKJVb_taFK_0No2T5J81+hJ8S8m-z-QE1=s...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

I have a function 'evalRule' that applies rules to steps in a backtracking
search optimization problem and evaluates the step's fitness or decides
that it must be eliminated entirely.

In the following, a result of Nothing means "eliminate the step," Just x
means the step has fitness score x.

evalRule :: Rule -> Step -> Maybe Double

I would like to write a function that applies a bunch of rules but
short-circuits the computation if it hits Nothing. However, unlike the way
the Maybe monad works, I want to know the partial results.

In the following, the rules are applied in order and the "Just" results are
collected up the point where a rule returns Nothing.

evalRules :: [Rule] -> Step -> [Double]

What's a nice way to do this?

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

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

Message: 3
Date: Fri, 30 Sep 2016 22:32:53 +0200
From: Imants Cekusins <ima...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] short-circuit like Maybe monad with a
        difference
Message-ID:
        <cap1qinzomu7laa7od1otgtfw+f3rjimufpalgtj-3jjrsjy...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

> short-circuits the computation if it hits Nothing. However, unlike the
way the Maybe monad works, I want to know the partial results.
​
could store partial results in a State monad.. Maybe would short circuit
but the values would stay in the State.

would this work?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20160930/d23634f8/attachment-0001.html>

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

Message: 4
Date: Fri, 30 Sep 2016 13:56:03 -0700
From: Dennis Raddle <dennis.rad...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] short-circuit like Maybe monad with a
        difference
Message-ID:
        <CAKxLvoqpToB3zceCodW7qEmB=xggDe7=96dqfecrfujhg9v...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

I just tried something



evalRules :: [Rule] -> Step -> [Double]
evalRules rules step = catMaybes . takeWhile isJust . map (flip evalRule
step) $ rules

This seems to work according to my testing.



On Fri, Sep 30, 2016 at 1:32 PM, Imants Cekusins <ima...@gmail.com> wrote:

> > short-circuits the computation if it hits Nothing. However, unlike the
> way the Maybe monad works, I want to know the partial results.
> ​
> could store partial results in a State monad.. Maybe would short circuit
> but the values would stay in the State.
>
> would this work?
>
> _______________________________________________
> 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/20160930/955100be/attachment-0001.html>

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

Message: 5
Date: Fri, 30 Sep 2016 23:12:44 +0200
From: Imants Cekusins <ima...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] short-circuit like Maybe monad with a
        difference
Message-ID:
        <cap1qinb217g3fuchthczlevwwzpst_ykhk7xv97adkr70r2...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

it is better alright.

is it necessary to know if all rules were evaluated?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20160930/15a0f928/attachment-0001.html>

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

Message: 6
Date: Fri, 30 Sep 2016 15:07:30 -0700
From: Dennis Raddle <dennis.rad...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] short-circuit like Maybe monad with a
        difference
Message-ID:
        <cakxlvoo_g7ud0ebec-_58lxfstz+rrpzjozmeygsp+qeyxp...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

It is necessary to know if all the rules are evaluated but that can be done
by checking the length of the output. Also I could do something like zip
the rule list with the [Double] output to tuple the rules together with
their scores.

D


On Fri, Sep 30, 2016 at 2:12 PM, Imants Cekusins <ima...@gmail.com> wrote:

> it is better alright.
>
> is it necessary to know if all rules were evaluated?
>
> _______________________________________________
> 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/20160930/bec67c8e/attachment-0001.html>

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

Message: 7
Date: Sat, 1 Oct 2016 12:54:26 +0800
From: Lai Boon Hui <laibo...@gmail.com>
To: beginners@haskell.org
Subject: [Haskell-beginners] Just wanted to share some GHCI macros
        with    fellow beginners
Message-ID:
        <CAJdQggmM2=ume0NeRNL=iwwvvxaoet3uspc7ughepnbmpvr...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi fellow beginners,

wanted to share some macros you can add to your ghci config file so that
you don't have to keep switching between ghci and command line. In my case
i use Git a lot

:def pwd (\_-> System.Directory.getCurrentDirectory >>= print >> return "")
:def gitA (\_ -> System.Process.rawSystem "git" ["add", "-A"] >>=
print >> return "")
:def gitC (\m -> System.Process.rawSystem "git" ["commit", "-am", m]
>>= print >> return "")
:def gitP (\_ -> System.Process.rawSystem "git" ["push"] >>= print >> return "")


-- 
Best Regards,
Boon Hui
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20161001/c9c779fe/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 100, Issue 1
*****************************************

Reply via email to