Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/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:  [Haskell-cafe] parser error in pattern (kolli kolli)
   2.  doubt....plz help me out (kolli kolli)
   3. Re:  [Haskell-cafe] parser error in pattern (Michael Xavier)
   4. Re:  doubt....plz help me out (jean verdier)
   5.  recursion and pattern matching (Alia)
   6. Re:  Non exhaustive pattern match not flagged? (Hugo Ferreira)
   7. Re:  newbie: Monad, equivalent notation using
      Control.Monad.guard (Hugo Ferreira)


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

Message: 1
Date: Mon, 17 Oct 2011 16:14:06 -0600
From: kolli kolli <nammukoll...@gmail.com>
Subject: Re: [Haskell-beginners] [Haskell-cafe] parser error in
        pattern
To: Ivan Lazar Miljenovic <ivan.miljeno...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <cae7d9k6ojj5yxehjht_ktz54-a9ncw5mxck7+bqqnae5djw...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

I didnt understand properly but made changes according to what I
understood..Its still giving me the same error

eval1(If t1 t2 t3) =  case (If t1 t2 t3) of
                    eval1(If t1 t2 t3) ->  Just t1


On Mon, Oct 17, 2011 at 4:10 PM, Ivan Lazar Miljenovic <
ivan.miljeno...@gmail.com> wrote:

> On 18 October 2011 09:08, kolli kolli <nammukoll...@gmail.com> wrote:
> > actual error message is
> >
> > homework2.lhs:137:20: parse error on input `where'
> >
> > data Term = Tru
> >           | Fls
> >           | If Term Term Term
> >           | Zero
> >           | Succ Term
> >           | Pred Term
> >           | IsZero Term
> >           deriving Eq
> >
>
> As I said, the error is from your incorrect usage of the case
> statement; it _should_ look something like:
>
> case foo of
>    bar -> baz
>    bar' -> baz'
>
> >
> >
> >
> >
> > On Mon, Oct 17, 2011 at 4:03 PM, Ivan Lazar Miljenovic
> > <ivan.miljeno...@gmail.com> wrote:
> >>
> >> On 18 October 2011 08:56, kolli kolli <nammukoll...@gmail.com> wrote:
> >> > after parsing a string i am evaluating it...
> >> > string if t1 then t2 else t3
> >> > my code is
> >> > eval1 :: Term ->  Maybe Term
> >> > eval1(If Tru t2 t3) = Just t2
> >> > eval1(If Fls t2 t3) = Just t3
> >> > eval1(If t1 t2 t3) =  case eval t1
> >> >                     where eval1(If t1 t2 t3) =  Just t1
> >> >
> >> > eval :: Term -> Term
> >> > eval (IsZero Zero) = Tru
> >> > eval (Zero) = Zero
> >> > eval(Pred Zero) = Pred Zero
> >>
> >> Your case statement is incomplete for starters...
> >>
> >> Can you please provide the actual error message as well?  Your
> >> definition of Term would also be useful.
> >>
> >> >
> >> > On Mon, Oct 17, 2011 at 3:46 PM, Ivan Lazar Miljenovic
> >> > <ivan.miljeno...@gmail.com> wrote:
> >> >>
> >> >> On 18 October 2011 08:43, kolli kolli <nammukoll...@gmail.com>
> wrote:
> >> >> > hey can anyone tell me what is parser error in parser??Plz help me
> >> >> > out
> >> >>
> >> >> It's when the parser can't parse what it's provided.... providing the
> >> >> code that caused the problem and the actual error message is required
> >> >> for a more detailed explanation.
> >> >>
> >> >> --
> >> >> Ivan Lazar Miljenovic
> >> >> ivan.miljeno...@gmail.com
> >> >> IvanMiljenovic.wordpress.com
> >> >
> >> >
> >>
> >>
> >>
> >> --
> >> Ivan Lazar Miljenovic
> >> ivan.miljeno...@gmail.com
> >> IvanMiljenovic.wordpress.com
> >
> >
>
>
>
> --
> Ivan Lazar Miljenovic
> ivan.miljeno...@gmail.com
> IvanMiljenovic.wordpress.com
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111017/81b66853/attachment-0001.htm>

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

Message: 2
Date: Mon, 17 Oct 2011 20:17:04 -0600
From: kolli kolli <nammukoll...@gmail.com>
Subject: [Haskell-beginners] doubt....plz help me out
To: beginners@haskell.org
Message-ID:
        <cae7d9k5txd9ghcfzo6orau-x4qkm2h+qdion0oykxc5tqb7...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

I am new to haskell plz dnt mind


scan :: [Char] -> Token
scan ('i':'f':tl)  = IfKeyword
scan ('t':'h':'e':'n':tl)  = ThenKeyword
scanp :: [Char] -> [Token]
scanp t  = sequence (map scan t)

when I call scan on my file which has "if then"
then its just printing if as IfKeyword ..its nt talking the then word

I tried using sequence but its nt working..Can you please help me out..

I have to get the output as a list of tokens

[IfKeyword, ThenKeyword]
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111017/77b994e2/attachment-0001.htm>

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

Message: 3
Date: Mon, 17 Oct 2011 19:20:45 -0700
From: Michael Xavier <nemesisdes...@gmail.com>
Subject: Re: [Haskell-beginners] [Haskell-cafe] parser error in
        pattern
To: kolli kolli <nammukoll...@gmail.com>
Cc: Ivan Lazar Miljenovic <ivan.miljeno...@gmail.com>,
        beginners@haskell.org
Message-ID:
        <CANk=zmEhXrGqwzJXKqZHw8CHEuWq9L=kp7u_u6wrxdj9q-n...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

I'm finding it really hard to grok what this is even supposed to do but you
have:

eval1(If t1 t2 t3) =  case (If t1 t2 t3) of
                    eval1(If t1 t2 t3) ->  Just t1


Case doesn't work that way. It would be something like:

eval1 (If t1 t2 t3) = case (some expression) of
                             pattern1 -> somevalue
                             pattern2 -> anothervalue

I don't see the intent of pattern matching the exact argument to eval1.

What is the type of eval1?

Also, your filename is homework2.hs. Please read this page on the Haskell
wiki:

http://www.haskell.org/haskellwiki/Homework_help

That's not to say you shouldn't ask these questions here but note that most
of us will not do your homework for you. We will provide hints, but you
should be doing your due diligence to try to understand what your code is
doing and possible reasons why it isn't working.
-- 
Michael Xavier
http://www.michaelxavier.net
LinkedIn <http://www.linkedin.com/pub/michael-xavier/13/b02/a26>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111017/8b86b70a/attachment-0001.htm>

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

Message: 4
Date: Tue, 18 Oct 2011 08:13:52 +0200
From: jean verdier <verdier.j...@gmail.com>
Subject: Re: [Haskell-beginners] doubt....plz help me out
To: kolli kolli <nammukoll...@gmail.com>
Cc: beginners@haskell.org
Message-ID: <1318918432.2338.2.camel@localhost.localdomain>
Content-Type: text/plain; charset="UTF-8"

You forgot to process the tail part of the scanned string. Do something
with the tl binding in the scan function. Note that the scan function
returns Token and not [Token].


On Mon, 2011-10-17 at 20:17 -0600, kolli kolli wrote:
> I am new to haskell plz dnt mind
> 
> 
> scan :: [Char] -> Token
> scan ('i':'f':tl)  = IfKeyword 
> scan ('t':'h':'e':'n':tl)  = ThenKeyword
> scanp :: [Char] -> [Token]
> scanp t  = sequence (map scan t) 
> 
> when I call scan on my file which has "if then"
> then its just printing if as IfKeyword ..its nt talking the then word
> 
> I tried using sequence but its nt working..Can you please help me
> out..
> 
> I have to get the output as a list of tokens
> 
> [IfKeyword, ThenKeyword] 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners





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

Message: 5
Date: Tue, 18 Oct 2011 01:34:14 -0700 (PDT)
From: Alia <alia_kho...@yahoo.com>
Subject: [Haskell-beginners] recursion and pattern matching
To: "beginners@haskell.org" <beginners@haskell.org>
Message-ID:
        <1318926854.22761.yahoomail...@web65714.mail.ac4.yahoo.com>
Content-Type: text/plain; charset=iso-8859-1

I have a question about what's the idiomatic way to walk a tree where there is 
also a requirement
for pattern-matching to draw variables out of the Node 'container':



<Test.hs>

module Test

where

data Tree a b = EmptyTree | Node a b [Tree a b] 
??????????? deriving (Show, Read, Eq)? 
? 
t =? Node "goal" 1.0 [
??????? Node "c1" 0.5 [
??????????? Node "c3" 3.0 [
??????????????? Node "c5" 1.0 []
??????????????? ]
??????????? ],
??????? Node "c2" 0.5 [
??????????? Node "c4" 2.0 []
??????????? ]
???? ]


sumTree :: (Num b) => Tree a b -> b
sumTree EmptyTree = 0
sumTree (Node _ value []) = value
sumTree (Node _ value [x]) = value + sumTree x
sumTree (Node name value (x:xs)) = value + sumTree x + sumTree (Node name 0 xs)

depth :: Tree a b -> Int
depth EmptyTree = 0
depth (Node _ _ []) = 1
depth (Node _ _ [x]) = 1 + depth x
depth (Node n v (x:xs)) = 1 + depth (Node n v xs)?

</Test.hs>

Interactively:

*Test> sumTree t
8.0
*Test> depth t
4
*Test> 


This seems to work, but I have a sense that one should use folds and fmap and 
that there
is a better and cleaner what to do this.

Any help would be much appreciated.

Thanks

AK



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

Message: 6
Date: Tue, 18 Oct 2011 09:52:57 +0100
From: Hugo Ferreira <h...@inescporto.pt>
Subject: Re: [Haskell-beginners] Non exhaustive pattern match not
        flagged?
To: Henk-Jan van Tuyl <hjgt...@chello.nl>
Cc: beginners@haskell.org
Message-ID: <4e9d3e69.4010...@inescporto.pt>
Content-Type: text/plain; charset=ISO-8859-15; format=flowed

On 10/17/2011 04:53 PM, Henk-Jan van Tuyl wrote:
> On Mon, 17 Oct 2011 17:39:49 +0200, Hugo Ferreira <h...@inescporto.pt>
> wrote:
>
>> f :: [a] -> [b] -> Int
>> --f [] _ = error "undefined for empty array"
>> f _ [] = error "undefined for empty array"
>> f (_:xs) (_:ys) = length xs + length ys
>>
>> I get a warning:
>>
>> Warning: Pattern match(es) are non-exhaustive
>> In an equation for `f': Patterns not matched: [] (_ : _)
>>
>> as expected. But for:
>>
>> bigrams :: [a] -> [[a]]
>> --bigrams [] = []
>> bigrams [_] = []
>> bigrams xs = take 2 xs : bigrams (tail xs)
>>
>> I don't. Why is the first predicate not detected as missing?
>
> The pattern in the line
> bigrams xs = take 2 xs : bigrams (tail xs)
> matches any list, even empty lists
>

Thank you.
Hugo F.

> Regards,
> Henk-Jan van Tuyl
>
>




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

Message: 7
Date: Tue, 18 Oct 2011 10:52:57 +0100
From: Hugo Ferreira <h...@inescporto.pt>
Subject: Re: [Haskell-beginners] newbie: Monad, equivalent notation
        using Control.Monad.guard
To: Brent Yorgey <byor...@seas.upenn.edu>
Cc: beginners@haskell.org
Message-ID: <4e9d4c79.9040...@inescporto.pt>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Hello,

On 10/17/2011 05:22 PM, Brent Yorgey wrote:
> On Mon, Oct 17, 2011 at 04:18:05PM +0100, Hugo Ferreira wrote:
>> Hello,
>>
>> I came across the following code:
>>
>> ngrams'' :: Int ->  [a] ->  [[a]]
>> ngrams'' n l = do
>>    t<- Data.List.tails l
>>    l<- [take n t]
>>    Control.Monad.guard (length l == n)
>>    return l
>>
>> and tried to use the ">>=" operator in order
>> to figure out how Monads work. I came up with:
>>
>> test l =
>>     (Data.List.tails l)
>>     >>= (\t ->  [take 2 t])
>>     >>= (\l ->  if (length l == 2) then [l] else [])
>>
>> Questions:
>> 1. How can I use Control.Monad.guard directly in "test l"
>
> test l =
>      (Data.List.tails l)
>      >>= \t ->  [take 2 t]
>      >>= \l ->  Control.Monad.guard (length l == 2)
>      >>   return l
>
> The rule is that
>
>    x<- foo
>
> desugars to
>
>    foo>>= \x ->  ...
>
> and
>
>    blah
>
> desugars to
>
>    blah>>  ...
>

Ok, I was not aware of the >>.

> One thing that might have been tripping you up is your extra
> parentheses around the lambda expressions.  If you have
>
>    >>= (\l ->  ...)
>    >>   foo...
>
> the l does not scope over foo... so you cannot mention it.  Instead
> what you want is
>
>    >>= \l ->  ...
>    >>   foo...
>
> so the lambda expression is actually   \l ->  ...>>  foo..., that is,
> it includes *everything* after the \l ->  ... and not just the stuff on
> that line.
>

Hmmm. Still cannot wrap my mind around this B-(.

[[1],[2],[3]] >>= \l -> func1 l >>= \m -> func2 m

\l will hold each of the 3 elements of initial list
    these are concatenated with the results of func1
    results in a new list

\m will have each element in the new list
    these are concatenated with the results of func2
    results in a last list

is equal to ?

(([[1],[2],[3]] >>= \l -> func1 l) >>= \m -> func2 m)

Hmmm.. going to lookup more info on this.

>> 2. Related issue: how can create a List monad so that I
>>     can input "l" argument of "test l" directly?
>
> I don't understand this question.  Can you give an example of what you
> are trying to do?
>

Weird. I was trying to execute:

test1' [[1,2,3],[2,3],[3]]

in a version that does not use Data.List.tails
but could not. Now it works. Must have done something
wrong.

Hugo F.


> -Brent
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>




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

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 40, Issue 26
*****************************************

Reply via email to