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.  Parsing a file (Roger Mason)
   2. Re:  Parsing a file (Francesco Ariis)
   3. Re:  Parsing a file (Roger Mason)
   4. Re:  Parsing a file (Francesco Ariis)
   5. Re:  Parsing a file (David McBride)


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

Message: 1
Date: Wed, 26 Jan 2022 08:40:10 -0330
From: Roger Mason <rma...@mun.ca>
To: <beginners@haskell.org>
Subject: [Haskell-beginners] Parsing a file
Message-ID: <y651r0uad18....@mun.ca>
Content-Type: text/plain

Hello,

Warning: long post.

I've worked my way through various parsing tutorials using either Parsec
or ReadP.  I reached a point where I need to try parsing one of the
types of file for which I'm writing the parser.  I have written parsers
for various parts of this file:

eqatoms.out:
======================================================

Species :    1 (Si)
 atom    1 is equivalent to atom(s)
   1   2   3
 atom    2 is equivalent to atom(s)
   1   2   3
 atom    3 is equivalent to atom(s)
   1   2   3

Species :    2 (O)
 atom    1 is equivalent to atom(s)
   1   2   3   4   5   6
 atom    2 is equivalent to atom(s)
   1   2   3   4   5   6
 atom    3 is equivalent to atom(s)
   1   2   3   4   5   6
 atom    4 is equivalent to atom(s)
   1   2   3   4   5   6
 atom    5 is equivalent to atom(s)
   1   2   3   4   5   6
 atom    6 is equivalent to atom(s)
   1   2   3   4   5   6

======================================================

These are my imports:
======================================================
  import qualified Text.Parsec as Parsec

  import Text.Parsec ((<?>))

  import Control.Applicative

  import Control.Monad.Identity (Identity)
======================================================

These are my parsers:
======================================================
   :{
    species :: Parsec.Parsec String () (String,String)
    species = do
     --Parsec.char 'S'
     Parsec.string "Species"
     Parsec.spaces
     Parsec.char ':'
     Parsec.spaces
     digits <- Parsec.many1 Parsec.digit
     Parsec.spaces
     Parsec.char '('
     id <- Parsec.many1 Parsec.letter
     return (id,digits)
   :}

   :{
    atom = do
     Parsec.spaces
     Parsec.string "atom"
     Parsec.spaces
     digits <- Parsec.digit
     return digits
   :}

:{
  equivalents = do
   Parsec.spaces
   digits <- Parsec.digit
   return digits
:}
======================================================

Some simple tests:
======================================================
src = "oops"
Parsec.parse species src "Species :    1 (Si)"

Right ("Si","1")

src = "Parsing_File/eqatoms.out"
Parsec.parse atom src "atom    5 is equivalent to atom(s)"

Right '5'

src = "Parsing_File/eqatoms.out"
Parsec.parse (Parsec.many1 equivalents) src "   1   2   3   4   5   6"

: Right "123456"
======================================================

So, the individual parsers work as intended.  However, parsing an actual
file does not work.

I define a function to return the file contents:
======================================================
   :{
     input = do
       eqatoms <- readFile "Parsing_File/eqatoms.out"
       return eqatoms
   :}
======================================================

A test shows that my reader works:
======================================================
input

: Species :    1 (Si)\n atom    1 is equivalent to atom(s)\n   1   2
3\n atom    2 is equivalent to atom(s)\n   1   2   3\n atom    3 is
equivalent to atom(s)\n   1   2   3\n\nSpecies :    2 (O)\n atom    1 is
equivalent to atom(s)\n   1   2   3   4   5   6\n atom    2 is
equivalent to atom(s)\n   1   2   3   4   5   6\n atom    3 is
equivalent to atom(s)\n   1   2   3   4   5   6\n atom    4 is
equivalent to atom(s)\n   1   2   3   4   5   6\n atom    5 is
equivalent to atom(s)\n   1   2   3   4   5   6\n atom    6 is
equivalent to atom(s)\n   1   2   3   4   5   6\n

======================================================

I attempt to parse the input:
======================================================
   :{
     main = do
     eqatoms <- readFile "Parsing_File/eqatoms.out"
     Parsec.parse species "test species" eqatoms
     return
   :}

Prelude Parsec Text.Parsec Control.Applicative Control.Monad.Identity| Prelude 
Parsec Text.Parsec Control.Applicative Control.Monad.Identity| Prelude Parsec 
Text.Parsec Control.Applicative Control.Monad.Identity| Prelude Parsec 
Text.Parsec Control.Applicative Control.Monad.Identity| Prelude Parsec 
Text.Parsec Control.Applicative Control.Monad.Identity| 
<interactive>:250:3: error:
    ,* Couldn't match type `Either Parsec.ParseError' with `IO'
      Expected type: IO (String, String)
        Actual type: Either Parsec.ParseError (String, String)
    ,* In a stmt of a 'do' block:
        Parsec.parse species "test species" eqatoms
      In the expression:
        do eqatoms <- readFile "Parsing_File/eqatoms.out"
           Parsec.parse species "test species" eqatoms
           return
      In an equation for `main':
          main
            = do eqatoms <- readFile "Parsing_File/eqatoms.out"
                 Parsec.parse species "test species" eqatoms
                 return

<interactive>:251:3: error:
    ,* Couldn't match expected type `IO b'
                  with actual type `a0 -> m0 a0'
    ,* Probable cause: `return' is applied to too few arguments
      In a stmt of a 'do' block: return
      In the expression:
        do eqatoms <- readFile "Parsing_File/eqatoms.out"
           Parsec.parse species "test species" eqatoms
           return
      In an equation for `main':
          main
            = do eqatoms <- readFile "Parsing_File/eqatoms.out"
                 Parsec.parse species "test species" eqatoms
                 return
    ,* Relevant bindings include
        main :: IO b (bound at <interactive>:248:3)
======================================================

Can someone please help me to get this to work?

Thanks for reading to the end of this very long post.
Roger


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

Message: 2
Date: Wed, 26 Jan 2022 13:58:41 +0100
From: Francesco Ariis <fa...@ariis.it>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] Parsing a file
Message-ID: <yfffgbxldw9y4...@mkiii.casa>
Content-Type: text/plain; charset=utf-8

Hello Roger,

Il 26 gennaio 2022 alle 08:40 Roger Mason ha scritto:
> I attempt to parse the input:
> ======================================================
>    :{
>      main = do
>      eqatoms <- readFile "Parsing_File/eqatoms.out"
>      Parsec.parse species "test species" eqatoms
>      return
>    :}
> 
> Prelude Parsec Text.Parsec Control.Applicative Control.Monad.Identity| 
> Prelude Parsec Text.Parsec Control.Applicative Control.Monad.Identity| 
> Prelude Parsec Text.Parsec Control.Applicative Control.Monad.Identity| 
> Prelude Parsec Text.Parsec Control.Applicative Control.Monad.Identity| 
> Prelude Parsec Text.Parsec Control.Applicative Control.Monad.Identity| 
> <interactive>:250:3: error:
>     ,* Couldn't match type `Either Parsec.ParseError' with `IO'
>       Expected type: IO (String, String)
>         Actual type: Either Parsec.ParseError (String, String)
>     ,* In a stmt of a 'do' block:
>         Parsec.parse species "test species" eqatoms
>       In the expression:
>         do eqatoms <- readFile "Parsing_File/eqatoms.out"
>            Parsec.parse species "test species" eqatoms
>            return
>       In an equation for `main':
>           main
>             = do eqatoms <- readFile "Parsing_File/eqatoms.out"
>                  Parsec.parse species "test species" eqatoms
>                  return

The problem is with this line

>      Parsec.parse species "test species" eqatoms

`parse` returns an Either, so you should pattern match on
its `Left` and `Right` (using `case` or the `either` function).
This has to be done inside a `let` too, because parse is a pure
function.
Does that help?
—F


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

Message: 3
Date: Wed, 26 Jan 2022 10:02:04 -0330
From: Roger Mason <rma...@mun.ca>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] Parsing a file
Message-ID: <y65wnim8vmx....@mun.ca>
Content-Type: text/plain

Hello Francesco,

Thanks for your response.

Francesco Ariis <fa...@ariis.it> writes:

>
> The problem is with this line
>
>>      Parsec.parse species "test species" eqatoms
>
> `parse` returns an Either, so you should pattern match on
> its `Left` and `Right` (using `case` or the `either` function).
> This has to be done inside a `let` too, because parse is a pure
> function.
> Does that help?

I'll need to check exactly how to use case for this, but before I do I
have this question.

=Parsec.parse species "test species" "this that"= worked fine in my
tests.  Why has `parse` changed changed its return type when invoked as

=Parsec.parse species "test species" eqatoms=

That is confusing (and off putting) and makes it hard to test ones code.

Thanks,
Roger


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

Message: 4
Date: Wed, 26 Jan 2022 15:43:43 +0100
From: Francesco Ariis <fa...@ariis.it>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] Parsing a file
Message-ID: <YfFeHxqW//ykf...@mkiii.casa>
Content-Type: text/plain; charset=utf-8

Il 26 gennaio 2022 alle 10:02 Roger Mason ha scritto:
> I'll need to check exactly how to use case for this, but before I do I
> have this question.
> 
> =Parsec.parse species "test species" "this that"= worked fine in my
> tests.  Why has `parse` changed changed its return type when invoked as
> 
> =Parsec.parse species "test species" eqatoms=
> 
> That is confusing (and off putting) and makes it hard to test ones code.

They work fine because — I suspect — you ran them *inside ghci* (which
is totally fine). When you are dealing with main (or any function inside
the IO monad) you need as usual to make things typecheck by providing
the correct data.

Simple quiz: do you understand why

    main :: IO ()
    main = "prova"

does nor work (nor compile) while

    main :: IO ()
    main = putStrLn "prova"

does? If you are not sure read the “I/O” section from Real World Haskell [1]
or any introductory material about Haskell and IO.
Keep learning & fire here again if you are not sure!
—F

[1] http://book.realworldhaskell.org/read/io.html


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

Message: 5
Date: Wed, 26 Jan 2022 12:29:40 -0500
From: David McBride <toa...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Parsing a file
Message-ID:
        <CAN+Tr411A=firfseum7aszq8rl4ymw5wzcvbjcwfdgqvrjv...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

These two pieces of code are not equivalent.

  :{
     input = do
       eqatoms <- readFile "Parsing_File/eqatoms.out"
       return eqatoms
   :}

   :{
     main = do
       eqatoms <- readFile "Parsing_File/eqatoms.out"
       Parsec.parse species "test species" eqatoms
     return
   :}

You will have to do something like
  :{
     main = do
       eqatoms <- readFile "Parsing_File/eqatoms.out"
       let res = Parsec.parse species "test species" eqatoms
       putStrLn (show res)
     return
   :}

And you will eventually clean it up by using a case statement to
distinguish between success and error.

On Wed, Jan 26, 2022 at 7:41 AM Roger Mason <rma...@mun.ca> wrote:

> Hello,
>
> Warning: long post.
>
> I've worked my way through various parsing tutorials using either Parsec
> or ReadP.  I reached a point where I need to try parsing one of the
> types of file for which I'm writing the parser.  I have written parsers
> for various parts of this file:
>
> eqatoms.out:
> ======================================================
>
> Species :    1 (Si)
>  atom    1 is equivalent to atom(s)
>    1   2   3
>  atom    2 is equivalent to atom(s)
>    1   2   3
>  atom    3 is equivalent to atom(s)
>    1   2   3
>
> Species :    2 (O)
>  atom    1 is equivalent to atom(s)
>    1   2   3   4   5   6
>  atom    2 is equivalent to atom(s)
>    1   2   3   4   5   6
>  atom    3 is equivalent to atom(s)
>    1   2   3   4   5   6
>  atom    4 is equivalent to atom(s)
>    1   2   3   4   5   6
>  atom    5 is equivalent to atom(s)
>    1   2   3   4   5   6
>  atom    6 is equivalent to atom(s)
>    1   2   3   4   5   6
>
> ======================================================
>
> These are my imports:
> ======================================================
>   import qualified Text.Parsec as Parsec
>
>   import Text.Parsec ((<?>))
>
>   import Control.Applicative
>
>   import Control.Monad.Identity (Identity)
> ======================================================
>
> These are my parsers:
> ======================================================
>    :{
>     species :: Parsec.Parsec String () (String,String)
>     species = do
>      --Parsec.char 'S'
>      Parsec.string "Species"
>      Parsec.spaces
>      Parsec.char ':'
>      Parsec.spaces
>      digits <- Parsec.many1 Parsec.digit
>      Parsec.spaces
>      Parsec.char '('
>      id <- Parsec.many1 Parsec.letter
>      return (id,digits)
>    :}
>
>    :{
>     atom = do
>      Parsec.spaces
>      Parsec.string "atom"
>      Parsec.spaces
>      digits <- Parsec.digit
>      return digits
>    :}
>
> :{
>   equivalents = do
>    Parsec.spaces
>    digits <- Parsec.digit
>    return digits
> :}
> ======================================================
>
> Some simple tests:
> ======================================================
> src = "oops"
> Parsec.parse species src "Species :    1 (Si)"
>
> Right ("Si","1")
>
> src = "Parsing_File/eqatoms.out"
> Parsec.parse atom src "atom    5 is equivalent to atom(s)"
>
> Right '5'
>
> src = "Parsing_File/eqatoms.out"
> Parsec.parse (Parsec.many1 equivalents) src "   1   2   3   4   5   6"
>
> : Right "123456"
> ======================================================
>
> So, the individual parsers work as intended.  However, parsing an actual
> file does not work.
>
> I define a function to return the file contents:
> ======================================================
>    :{
>      input = do
>        eqatoms <- readFile "Parsing_File/eqatoms.out"
>        return eqatoms
>    :}
> ======================================================
>
> A test shows that my reader works:
> ======================================================
> input
>
> : Species :    1 (Si)\n atom    1 is equivalent to atom(s)\n   1   2
> 3\n atom    2 is equivalent to atom(s)\n   1   2   3\n atom    3 is
> equivalent to atom(s)\n   1   2   3\n\nSpecies :    2 (O)\n atom    1 is
> equivalent to atom(s)\n   1   2   3   4   5   6\n atom    2 is
> equivalent to atom(s)\n   1   2   3   4   5   6\n atom    3 is
> equivalent to atom(s)\n   1   2   3   4   5   6\n atom    4 is
> equivalent to atom(s)\n   1   2   3   4   5   6\n atom    5 is
> equivalent to atom(s)\n   1   2   3   4   5   6\n atom    6 is
> equivalent to atom(s)\n   1   2   3   4   5   6\n
>
> ======================================================
>
> I attempt to parse the input:
> ======================================================
>    :{
>      main = do
>      eqatoms <- readFile "Parsing_File/eqatoms.out"
>      Parsec.parse species "test species" eqatoms
>      return
>    :}
>
> Prelude Parsec Text.Parsec Control.Applicative Control.Monad.Identity|
> Prelude Parsec Text.Parsec Control.Applicative Control.Monad.Identity|
> Prelude Parsec Text.Parsec Control.Applicative Control.Monad.Identity|
> Prelude Parsec Text.Parsec Control.Applicative Control.Monad.Identity|
> Prelude Parsec Text.Parsec Control.Applicative Control.Monad.Identity|
> <interactive>:250:3: error:
>     ,* Couldn't match type `Either Parsec.ParseError' with `IO'
>       Expected type: IO (String, String)
>         Actual type: Either Parsec.ParseError (String, String)
>     ,* In a stmt of a 'do' block:
>         Parsec.parse species "test species" eqatoms
>       In the expression:
>         do eqatoms <- readFile "Parsing_File/eqatoms.out"
>            Parsec.parse species "test species" eqatoms
>            return
>       In an equation for `main':
>           main
>             = do eqatoms <- readFile "Parsing_File/eqatoms.out"
>                  Parsec.parse species "test species" eqatoms
>                  return
>
> <interactive>:251:3: error:
>     ,* Couldn't match expected type `IO b'
>                   with actual type `a0 -> m0 a0'
>     ,* Probable cause: `return' is applied to too few arguments
>       In a stmt of a 'do' block: return
>       In the expression:
>         do eqatoms <- readFile "Parsing_File/eqatoms.out"
>            Parsec.parse species "test species" eqatoms
>            return
>       In an equation for `main':
>           main
>             = do eqatoms <- readFile "Parsing_File/eqatoms.out"
>                  Parsec.parse species "test species" eqatoms
>                  return
>     ,* Relevant bindings include
>         main :: IO b (bound at <interactive>:248:3)
> ======================================================
>
> Can someone please help me to get this to work?
>
> Thanks for reading to the end of this very long post.
> Roger
> _______________________________________________
> 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/20220126/88629188/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 162, Issue 1
*****************************************

Reply via email to