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.  newbie: Monad,   equivalent notation using Control.Monad.guard
      (Hugo Ferreira)
   2.  Non exhaustive pattern match not flagged? (Hugo Ferreira)
   3. Re:  Non exhaustive pattern match not flagged? (Henk-Jan van Tuyl)
   4. Re:  newbie: Monad, equivalent notation using
      Control.Monad.guard (Brent Yorgey)
   5.  creating a relational tuple type (AM)
   6.  GHC as a library error. (Paulo Pocinho)
   7.  Fwd: parser error in pattern (kolli kolli)
   8. Re:  Fwd: parser error in pattern (Michael Xavier)
   9. Re:  creating a relational tuple type (Stephen Tetley)
  10. Re:  [Haskell-cafe] parser error in pattern (kolli kolli)


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

Message: 1
Date: Mon, 17 Oct 2011 16:18:05 +0100
From: Hugo Ferreira <h...@inescporto.pt>
Subject: [Haskell-beginners] newbie: Monad,     equivalent notation using
        Control.Monad.guard
To: beginners@haskell.org
Message-ID: <4e9c472d.8030...@inescporto.pt>
Content-Type: text/plain; charset=ISO-8859-15; format=flowed

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"
2. Related issue: how can create a List monad so that I
    can input "l" argument of "test l" directly?

TIA,
Hugo F.



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

Message: 2
Date: Mon, 17 Oct 2011 16:39:49 +0100
From: Hugo Ferreira <h...@inescporto.pt>
Subject: [Haskell-beginners] Non exhaustive pattern match not flagged?
To: beginners@haskell.org
Message-ID: <4e9c4c45.6020...@inescporto.pt>
Content-Type: text/plain; charset=ISO-8859-15; format=flowed

Hello,

I am using the GHC compiler with the -W flag.
When I compile:

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?

TIA,
Hugo F.



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

Message: 3
Date: Mon, 17 Oct 2011 17:53:38 +0200
From: "Henk-Jan van Tuyl" <hjgt...@chello.nl>
Subject: Re: [Haskell-beginners] Non exhaustive pattern match not
        flagged?
To: beginners@haskell.org, "Hugo Ferreira" <h...@inescporto.pt>
Message-ID: <op.v3h6fojupz0...@zen5.arnhem.chello.nl>
Content-Type: text/plain; charset=iso-8859-15; format=flowed;
        delsp=yes

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

Regards,
Henk-Jan van Tuyl


-- 
http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
--



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

Message: 4
Date: Mon, 17 Oct 2011 12:22:21 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] newbie: Monad, equivalent notation
        using Control.Monad.guard
To: beginners@haskell.org
Message-ID: <20111017162221.ga20...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

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 >> ...

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.

> 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?

-Brent



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

Message: 5
Date: Mon, 17 Oct 2011 15:51:07 -0400
From: AM <age...@themactionfaction.com>
Subject: [Haskell-beginners] creating a relational tuple type
To: beginners@haskell.org
Message-ID:
        <ab360203-59e0-492f-b146-3c3bb7bcb...@themactionfaction.com>
Content-Type: text/plain; charset=us-ascii

Hello,

As an effort to learn Haskell, I am creating a relational algebra engine. To 
this end, I have been looking at how haskelldb handles its mapping layer. I 
found this:

data RecNil = RecNil deriving (Eq, Ord)
data RecCons f a b = RecCons a b deriving (Eq, Ord)

It seems to me that the type of "b" is too loose, no? I would like "b" to be of 
the type RecCons or RecNil as well. The looseness of b prevents me from writing 
functions like this:

data RecCons a b = RecCons a b |
                     RecNil
                     deriving (Eq, Ord)

tupleLength :: RecCons a b -> Int
tupleLength RecNil = 0
tupleLength (RecCons x xs) = 1 + tupleLength xs -- xs really should be of type 
RecCons

What I would like is a list of arbitrary values rolled into a type such as 
(RecCons Int (RecCons String RecNil)). 

I tried a RecCons with existential quantification, but I ended up with a 
completely loosely-typed list. I would like Haskell's type engine to catch 
invalid comparisons between record tuples of disparate types. It seems that 
HDBRec works around this using a variety of typeclasses, but I don't really 
understand why.

Thanks for any advice.

Cheers,
M





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

Message: 6
Date: Mon, 17 Oct 2011 21:55:06 +0100
From: Paulo Pocinho <poci...@gmail.com>
Subject: [Haskell-beginners] GHC as a library error.
To: beginners@haskell.org
Message-ID:
        <cak4i1qspo1v0emwdt8zsz_abdbiorpbuwvs7-zon2i1nj1n...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

I'm trying GHC as a library, as documented in:

http://www.haskell.org/haskellwiki/GHC/As_a_library
http://www.haskell.org/ghc/docs/7.2.1/html/users_guide/ghc-as-a-library.html

However, this code:

import GHC
import GHC.Paths ( libdir )
import DynFlags ( defaultDynFlags )

main =
    defaultErrorHandler defaultDynFlags $ do
      runGhc (Just libdir) $ do
        dflags <- getSessionDynFlags
        setSessionDynFlags dflags
        target <- guessTarget "test_main.hs" Nothing
        setTargets [target]
        load LoadAllTargets


Produces:

Couldn't match expected type `Severity'
            with actual type `DynFlags.Settings'
Expected type: DynFlags.LogAction
  Actual type: DynFlags.Settings -> DynFlags
In the first argument of `defaultErrorHandler', namely
  `defaultDynFlags'
In the expression: defaultErrorHandler defaultDynFlags


How can I fix it?



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

Message: 7
Date: Mon, 17 Oct 2011 15:43:47 -0600
From: kolli kolli <nammukoll...@gmail.com>
Subject: [Haskell-beginners] Fwd: parser error in pattern
To: haskell-c...@haskell.org, beginners@haskell.org
Message-ID:
        <cae7d9k6bshpyil6qdewqzh1hf8f9xelrrrwvgyjfkfqjrv5...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

---------- Forwarded message ----------
From: kolli kolli <nammukoll...@gmail.com>
Date: Mon, Oct 17, 2011 at 3:43 PM
Subject: parser error in pattern
To: haskell-c...@haskell.org


hey can anyone tell me what is parser error in pattern??Plz help me out
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111017/c910d1b9/attachment-0001.htm>

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

Message: 8
Date: Mon, 17 Oct 2011 14:47:00 -0700
From: Michael Xavier <nemesisdes...@gmail.com>
Subject: Re: [Haskell-beginners] Fwd: parser error in pattern
To: kolli kolli <nammukoll...@gmail.com>
Cc: beginners@haskell.org, haskell-c...@haskell.org
Message-ID:
        <CANk=zmH_MBX0exL0i76U=zn0xvzepfqq+2dv+0z74jq+c_e...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

You need to provide a code sample in order for someone to help you out.
Also, for small issues like this, it is sometimes best to go to #haskell on
irc.freenode.net and ask there.

On Mon, Oct 17, 2011 at 2:43 PM, kolli kolli <nammukoll...@gmail.com> wrote:

>
>
> ---------- Forwarded message ----------
> From: kolli kolli <nammukoll...@gmail.com>
> Date: Mon, Oct 17, 2011 at 3:43 PM
> Subject: parser error in pattern
> To: haskell-c...@haskell.org
>
>
> hey can anyone tell me what is parser error in pattern??Plz help me out
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>


-- 
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/cb785352/attachment-0001.htm>

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

Message: 9
Date: Mon, 17 Oct 2011 23:07:49 +0100
From: Stephen Tetley <stephen.tet...@gmail.com>
Subject: Re: [Haskell-beginners] creating a relational tuple type
Cc: beginners@haskell.org
Message-ID:
        <CAB2TPRB6Swv5feg9v9tSPhfx_q37xft=jDOXpy=50sH76=g...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

The type classes in Haskell DB are to allow manipulations on type level lists.

You probably want to read the paper "Strongly typed heterogeneous
collections" by Oleg Kiselyov, Ralf L?mmel, and Keean Schupke to get a
sense of Haskell DB:

http://homepages.cwi.nl/~ralf/HList/

To learn Haskell, writing a "less typed" relational algebra engine
would be significantly easier. The early sections of the HList give
simpler heterogeneous lists that don't use type level programming (but
aren't as well typed).



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

Message: 10
Date: Mon, 17 Oct 2011 16:08:42 -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:
        <cae7d9k6y4fygootgvdddkrngiryzr9uglqjkxppsb8v4rys...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

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





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
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111017/6ba75628/attachment.htm>

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

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


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

Reply via email to