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.  parse block comments (mike h)
   2. Re:  parse block comments (Francesco Ariis)
   3. Re:  parse block comments (mike h)
   4. Re:  parse block comments (mike h)
   5.  State, StateT, or ST for game settings? (Dave Martin)
   6. Re:  State, StateT, or ST for game settings? (Francesco Ariis)


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

Message: 1
Date: Sat, 18 Mar 2017 21:11:20 +0000
From: mike h <mike_k_hough...@yahoo.co.uk>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: [Haskell-beginners] parse block comments
Message-ID: <c3fadf0f-a3f8-4338-a4d1-9fb1101fe...@yahoo.co.uk>
Content-Type: text/plain; charset=utf-8

Hi,

Below is code I’m building up  for simple monadic and applicative parsers  from 
first principles.

I’ve just added code for single line Haskell style comments.

-- comment being '--'
comment :: Parser ()
comment = do
      string "--" 
      many (sat ( /='\n') )
      return ()

— or as applicative 
comment' = string "--" *> many (sat (/='\n') )


I’d really appreciate help on writing a function for multi line comments! “{-“  
and end with “-}”
I know I need some sort of look ahead but can’t quite get the feel of how!

Thanks 
Mike

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


import Control.Applicative
import Data.Char

newtype Parser a = P (String -> [(a,String)])

parse :: Parser a -> String -> [(a,String)]
parse (P p)  = p

item :: Parser Char
item = P (\s -> case s of
                    []     -> []
                    (x:xs) -> [(x, xs)])

instance Functor Parser where
    -- fmap :: (a -> b) -> f a -> f b
    fmap g p  = P (\inp -> case parse p inp of
                             [] -> []
                             [(x, xs)] -> [(g x, xs)])


instance Applicative Parser where
  -- pure :: a -> Parser a
  -- (<*>) :: Parser (a -> b) -> Parser a -> Parser b
  pure x = P (\inp -> [(x, inp)])
  pab <*> pa = P (\inp -> case parse pab inp of
                    [] -> []
                    [(aTob, out)] -> parse (fmap aTob pa) out)


three :: Parser (Char, Char)
three = pure g <*> item <*> item <*> item 
         where g x y z = (x, z)

instance Monad Parser where
   -- return :: a -> Parser a
   return x = P (\inp -> [(x, inp)])
   -- (>>=) :: Parser a -> (a -> Parser b) -> Parser b
   pa >>= f = P (\inp -> case parse pa inp of
                  [] -> []
                  [(a, out)] -> parse (f a) out)

instance Alternative Parser where
    -- empty :: Parser a
    empty = P (\inp -> [])
    -- (<|>) :: Parser a-> Parser a -> Parser a   
    -- if p1 works the that one otherwise p2 
    p1 <|> p2 = P (\inp -> case parse p1 inp of
                        []  -> parse p2 inp
                        out -> out)

sat :: (Char -> Bool) -> Parser Char
sat p = do
    x <- item
    if p x then return x else empty

digit :: Parser Char
digit = sat isDigit

lower :: Parser Char
lower = sat isLower

upper :: Parser Char
upper = sat isUpper

letter :: Parser Char
letter = sat isAlpha

alphanum :: Parser Char
alphanum = sat isAlphaNum

char :: Char -> Parser Char
char x = sat (==x)

string :: String -> Parser String
string [] = return []
string s@(x:xs) = do
    char x *> string xs *> return s

ident :: Parser String
ident = do
    x  <- lower
    xs <- many alphanum
    return (x:xs) 

ident' :: Parser String
ident' = pure (:) <*> lower <*> many alphanum
    
nat :: Parser Int 
nat = do
  xs <- some digit
  return (read xs)   

nat' :: Parser Int 
nat' = pure read <*> some digit

space :: Parser ()
space = do
    many (sat isSpace )
    return ()

space' :: Parser ()
space' = many (sat isSpace ) *> return ()

int :: Parser Int
int = do
    char '-'
    n <- nat
    return (-n)
    <|> nat

int' :: Parser Int
int' = char '-' *> pure ((-1)*) <*> nat <|> nat

token :: Parser a -> Parser a
token p = do 
    space 
    v <- p
    space
    return v

token' :: Parser a -> Parser a
token' p = space *> p <* space

identifier :: Parser String
identifier = token ident

natural :: Parser Int
natural = token nat

integer :: Parser Int
integer = token int

symbol :: String -> Parser String
symbol xs = token (string xs)


nats :: Parser [Int]
nats = do
    symbol "["
    n  <- natural
    ns <- many ( do symbol "," 
                    natural )
    symbol "]"
    return (n:ns)



-- comment being '--'
comment :: Parser ()
comment = do
      string "--" 
      many (sat ( /='\n') )
      return ()

comment' = string "--" *> many (sat (/='\n') )


nats' :: Parser [Int]
-- sequence and ignore "[" and the rest
-- the rest is fmap list cons into result of natural and the apply that to many 
others and
-- finally ignore the closing "]"  
nats' = symbol "[" >> (:) <$> natural <*> many (symbol "," >> natural) <* 
symbol "]"




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

Message: 2
Date: Sat, 18 Mar 2017 22:47:15 +0100
From: Francesco Ariis <fa...@ariis.it>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] parse block comments
Message-ID: <20170318214715.ga14...@casa.casa>
Content-Type: text/plain; charset=utf-8

On Sat, Mar 18, 2017 at 09:11:20PM +0000, mike h wrote:
> Hi,
> 
> Below is code I’m building up  for simple monadic and applicative parsers
> from first principles.

Hello Mike,
    You might want to check `manyTill` from Parsec to get an idea:

    manyTill :: (Stream s m t) => ParsecT s u m a -> ParsecT s u m end -> 
ParsecT s u m [a]
    manyTill p end      = scan
        where
              scan  = do { end; return [] } <|>
                      do { x <- p; xs <- scan; return (x:xs) }


The 'trick' lies in <|> (alternative). Does that help?


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

Message: 3
Date: Sat, 18 Mar 2017 22:22:25 +0000
From: mike h <mike_k_hough...@yahoo.co.uk>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] parse block comments
Message-ID: <7f565336-cb41-40ab-8ac8-250fc5efc...@yahoo.co.uk>
Content-Type: text/plain; charset="utf-8"

Hi Francesco,
:)

Yes! That really did help.
Will post later when I’ve tidied what I’ve done  but it seems correct.

Thank you.
M



> On 18 Mar 2017, at 21:47, Francesco Ariis <fa...@ariis.it> wrote:
> 
> On Sat, Mar 18, 2017 at 09:11:20PM +0000, mike h wrote:
>> Hi,
>> 
>> Below is code I’m building up  for simple monadic and applicative parsers
>> from first principles.
> 
> Hello Mike,
>    You might want to check `manyTill` from Parsec to get an idea:
> 
>    manyTill :: (Stream s m t) => ParsecT s u m a -> ParsecT s u m end -> 
> ParsecT s u m [a]
>    manyTill p end      = scan
>        where
>              scan  = do { end; return [] } <|>
>                      do { x <- p; xs <- scan; return (x:xs) }
> 
> 
> The 'trick' lies in <|> (alternative). Does that help?
> _______________________________________________
> 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/20170318/c0fe08b2/attachment-0001.html>

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

Message: 4
Date: Sat, 18 Mar 2017 22:49:11 +0000
From: mike h <mike_k_hough...@yahoo.co.uk>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] parse block comments
Message-ID: <ab704f77-ce0b-4ec5-b0fa-a1b357f60...@yahoo.co.uk>
Content-Type: text/plain; charset=utf-8

Monadic and applicative.

blockCmnt :: Parser ()
blockCmnt = do
  string "{-"
  manyTill item (string "-}")
  return ()

manyTill p endp = scan where
  scan = do 
           endp
           return []
           <|>
           do
            x <- p
            xs <- scan
            return (x:xs)


blockCmnt' :: Parser () 
blockCmnt' = string "{-" >> manyTill item (string "-}") >> return ()

manyTill' p endp = scan' where
  scan' = endp *> return [] <|> pure (:) <*> p <*> scan’

Thanks.
M

> On 18 Mar 2017, at 21:47, Francesco Ariis <fa...@ariis.it> wrote:
> 
> On Sat, Mar 18, 2017 at 09:11:20PM +0000, mike h wrote:
>> Hi,
>> 
>> Below is code I’m building up  for simple monadic and applicative parsers
>> from first principles.
> 
> Hello Mike,
>    You might want to check `manyTill` from Parsec to get an idea:
> 
>    manyTill :: (Stream s m t) => ParsecT s u m a -> ParsecT s u m end -> 
> ParsecT s u m [a]
>    manyTill p end      = scan
>        where
>              scan  = do { end; return [] } <|>
>                      do { x <- p; xs <- scan; return (x:xs) }
> 
> 
> The 'trick' lies in <|> (alternative). Does that help?
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners



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

Message: 5
Date: Sat, 18 Mar 2017 20:42:38 -0400
From: Dave Martin <davemartin...@aol.com>
To: beginners@haskell.org
Subject: [Haskell-beginners] State, StateT, or ST for game settings?
Message-ID: <15ae4041ade-58a-8...@webprd-a58.mail.aol.com>
Content-Type: text/plain; charset="utf-8"

I would like to create a game with a "main menu" offering the user a choice of 
"playing the game" or accessing a "settings menu," in which he can change 
defaults that would affect the game play (e.g. board size, etc.).

I know (barely) enough about the "IO monad" to write the menus and the basic 
gameplay, but what device do I need in order to manage the settings? A State 
monad? A StateT monad transformer? An ST monad? None of the above? I have some 
basic familiarity with the first two, but not enough to really grasp how they 
are actually used.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20170318/2fb5186c/attachment-0001.html>

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

Message: 6
Date: Sun, 19 Mar 2017 01:59:05 +0100
From: Francesco Ariis <fa...@ariis.it>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] State, StateT, or ST for game
        settings?
Message-ID: <20170319005905.ga3...@casa.casa>
Content-Type: text/plain; charset=us-ascii

On Sat, Mar 18, 2017 at 08:42:38PM -0400, Dave Martin wrote:
> I would like to create a game with a "main menu" offering the user a choice 
> of "playing the game" or accessing a "settings menu," in which he can change 
> defaults that would affect the game play (e.g. board size, etc.).
> 
> I know (barely) enough about the "IO monad" to write the menus and the basic 
> gameplay, but what device do I need in order to manage the settings? A State 
> monad? A StateT monad transformer? An ST monad? None of the above? I have 
> some basic familiarity with the first two, but not enough to really grasp how 
> they are actually used.

Hello Dave,
    State will do! Of course if you need to mix the two monads (State +
IO) you need a State transformer (StateT)
-F


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

Subject: Digest Footer

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


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

End of Beginners Digest, Vol 105, Issue 7
*****************************************

Reply via email to