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. Re:  State monad to help pass around game settings (David McBride)
   2. Re:  State monad to help pass around game settings
      (i.caught....@gmail.com)
   3.  Same code, system, but different arch using Win32 for
      reading registry. (Akos Marton)


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

Message: 1
Date: Fri, 7 Apr 2017 08:33:10 -0400
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] State monad to help pass around game
        settings
Message-ID:
        <can+tr436hu9ffok43wtuh4fn4qn63v_en4sdzuueu9d2kw8...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

The basic outline for using StateT for settings is the following.
Hopefully this will give you an idea of how to get started.

import Control.Monad.State

data Color = White | Red deriving (Enum, Show)
data Shape = Square deriving (Enum, Show)

data Stuff = Stuff deriving Show

data Settings = Settings {
  sColor :: Color,
  sShape :: Shape
} deriving Show

data MyApp = MyApp {
  settings :: Settings,
  otherStuff :: Stuff
} deriving Show

main = do
  (_, settings) <- runStateT  proc (MyApp (Settings White Square) Stuff)
  print settings


-- A reusable prompt function.
prompt :: String -> [a] -> (Char -> a) -> IO a
prompt question opts c2r = do
  putStrLn question
  mapM undefined opts
  c <- getChar
  let r = c2r c -- turn a Char into a Shape or a Color.
  return r

proc :: StateT MyApp IO ()
proc = do
  getColor
  getShape

getColor :: StateT MyApp IO ()
getColor = do
  color <- liftIO $ prompt "What color would you like?" [Red, White] undefined
  MyApp settings otherstuff <- get
  put $ (MyApp (settings { sColor = color })) otherstuff

getShape :: StateT MyApp IO ()
getShape = undefined

On Thu, Apr 6, 2017 at 9:26 PM, Dave Martin <davemartin...@aol.com> wrote:
> I'm trying to write a game with a "settings menu" where the user can adjust
> gameplay options. Right now I pass all the settings around as parameters.
> I'm trying to figure out how to use the State monad to simplify this task,
> but I can't figure out how to start. Or maybe my whole design approach is
> wrongheaded, and not in keeping with best practices. Haskell is my first
> language. This is the kind of thing I have now:
>
> mainM color shape =
>   putStrLn "\n\nMain Menu" >>
>   (putStrLn . unlines) [
>     "(1) Set",
>     "(2) Display",
>     "(3) Quit"] >>
>   putStr "? " >>
>   getChar >>= \c ->
>     case c of
>       '1' -> set color shape
>       '2' -> display color shape
>       '3' -> return ()
>       _ -> mainM color shape
>
> set color shape =
>   putStrLn "\n\nSettings" >>
>   (putStrLn . unlines) [
>     "(1) Color",
>     "(2) Shape",
>     "(3) Main Menu"] >>
>   putStr "? " >>
>   getChar >>= \c ->
>     case c of
>       '1' -> setColor color shape
>       '2' -> setShape color shape
>       '3' -> mainM color shape
>       _ -> set color shape
>
> setColor color shape =
>   putStr ("\n\nColor is " ++ color ++ ". New color? ") >>
>   getLine >>= \cs ->
>   set cs shape
>
> setShape color shape =
>   putStr ("\n\nShape is " ++ shape ++ ". New shape? ") >>
>   getLine >>= \cs ->
>   set color cs
>
> display color shape =
>   putStrLn ("\n\nColor is " ++ color ++ ". Shape is " ++ shape ++ ".") >>
>   mainM color shape
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>


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

Message: 2
Date: Fri, 7 Apr 2017 08:41:01 -0400
From: <i.caught....@gmail.com>
To: David McBride <toa...@gmail.com>,  The Haskell-Beginners Mailing
        List - Discussion of primarily beginner-level topics related to
        Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] State monad to help pass around game
        settings
Message-ID: <58e788db.1249240a.acda0.b...@mx.google.com>
Content-Type: text/plain; charset="utf-8"

I have a metro to catch but small interesting additions worth looking into:

Using `modify` and lenses, you get niceties like this to update the state:

modify $ scolor .~ color

Don’t forget to use ReaderT over StateT if you only need some configuration to 
be passed implicitly and wont mutate.

Last note, `StateT s m a` relies fairly heavily on understanding the essence of 
monads. Your goal is to build a computation in which you’re given the ability 
to keep and mutate a state `s`. At the end of the day, something has to “run” 
that computation, which will carry out its effects `m`. produce a 
result `a`, and possibly give you the final state `s` if needed as well. (See 
runStateT vs. execStateT vs. evalStateT).

Cheers,
Alex.

From: David McBride
Sent: April 7, 2017 8:34 AM
To: The Haskell-Beginners Mailing List - Discussion of primarily beginner-level 
topics related to Haskell
Subject: Re: [Haskell-beginners] State monad to help pass around game settings

The basic outline for using StateT for settings is the following.
Hopefully this will give you an idea of how to get started.

import Control.Monad.State

data Color = White | Red deriving (Enum, Show)
data Shape = Square deriving (Enum, Show)

data Stuff = Stuff deriving Show

data Settings = Settings {
  sColor :: Color,
  sShape :: Shape
} deriving Show

data MyApp = MyApp {
  settings :: Settings,
  otherStuff :: Stuff
} deriving Show

main = do
  (_, settings) <- runStateT  proc (MyApp (Settings White Square) Stuff)
  print settings


-- A reusable prompt function.
prompt :: String -> [a] -> (Char -> a) -> IO a
prompt question opts c2r = do
  putStrLn question
  mapM undefined opts
  c <- getChar
  let r = c2r c -- turn a Char into a Shape or a Color.
  return r

proc :: StateT MyApp IO ()
proc = do
  getColor
  getShape

getColor :: StateT MyApp IO ()
getColor = do
  color <- liftIO $ prompt "What color would you like?" [Red, White] undefined
  MyApp settings otherstuff <- get
  put $ (MyApp (settings { sColor = color })) otherstuff

getShape :: StateT MyApp IO ()
getShape = undefined

On Thu, Apr 6, 2017 at 9:26 PM, Dave Martin <davemartin...@aol.com> wrote:
> I'm trying to write a game with a "settings menu" where the user can adjust
> gameplay options. Right now I pass all the settings around as parameters.
> I'm trying to figure out how to use the State monad to simplify this task,
> but I can't figure out how to start. Or maybe my whole design approach is
> wrongheaded, and not in keeping with best practices. Haskell is my first
> language. This is the kind of thing I have now:
>
> mainM color shape =
>   putStrLn "\n\nMain Menu" >>
>   (putStrLn . unlines) [
>     "(1) Set",
>     "(2) Display",
>     "(3) Quit"] >>
>   putStr "? " >>
>   getChar >>= \c ->
>     case c of
>       '1' -> set color shape
>       '2' -> display color shape
>       '3' -> return ()
>       _ -> mainM color shape
>
> set color shape =
>   putStrLn "\n\nSettings" >>
>   (putStrLn . unlines) [
>     "(1) Color",
>     "(2) Shape",
>     "(3) Main Menu"] >>
>   putStr "? " >>
>   getChar >>= \c ->
>     case c of
>       '1' -> setColor color shape
>       '2' -> setShape color shape
>       '3' -> mainM color shape
>       _ -> set color shape
>
> setColor color shape =
>   putStr ("\n\nColor is " ++ color ++ ". New color? ") >>
>   getLine >>= \cs ->
>   set cs shape
>
> setShape color shape =
>   putStr ("\n\nShape is " ++ shape ++ ". New shape? ") >>
>   getLine >>= \cs ->
>   set color cs
>
> display color shape =
>   putStrLn ("\n\nColor is " ++ color ++ ". Shape is " ++ shape ++ ".") >>
>   mainM color shape
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
_______________________________________________
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/20170407/1b6a674d/attachment-0001.html>

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

Message: 3
Date: Fri, 7 Apr 2017 18:51:31 -0100
From: Akos Marton <makos...@gmail.com>
To: beginners@haskell.org
Cc: haskell-c...@haskell.org
Subject: [Haskell-beginners] Same code, system, but different arch
        using Win32 for reading registry.
Message-ID: <4cc23963-f3b5-881a-c6b6-60ce6b1fb...@gmail.com>
Content-Type: text/plain; charset="utf-8"; Format="flowed"

Dear Haskellers,

The setup:
Having a binary compiled on either x86 or x64 system (same installation, 
utilizing stack) in order to preserve compatibility against x64 systems. 
Actually, not to have 2 separate executable for each, that would be the 
overall goal. However it surprises me when running the x86 .exe 
utilizing Win32-2.5.4.1 package with ghc-8.0.2, reading out a registry 
key fails on x64 system with the following:/
/

/me.exe: RegOpenKey: invalid argument (The system cannot find the file 
specified.)/

That would be fine, however the key does exists. When same code, same 
system, but the .exe built to be x64 it runs like a charm.

A couple of question, which some of them eventually will not make sense, 
but still:
- Can it be ghc code optimization issue?
- but this is a runtime check in IO, if so, how?
- Yes, I could use a built-in windows system command and parse the input 
of that; unless absolutely necessary I would not introduce another 
dependency (system package). Would love to solve it with the currently 
utilized weapons.
- the issue just puzzles me... I would know the answer if possible.
- Is it more library (Win32), ghc, binary I generate, issue?

What library can I use to detect a system's architecture which works in 
this scenario?

Another thing which convoluted in the issue...
The function, /getSystemInfo :: IO SYSTEM_INFO, /can read out the 
underlying architecture. When compiled on x86 and run on x64 it would 
tell me: "I am running on x86". That's failure.

Most importantly: what is the obvious I am missing?

Thank you for your insights!
Best, Akos



Ps.: Would you/we need sample code to puzzle about I can quickly weld 
one. - not sure if necessary.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20170407/f0187166/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 106, Issue 3
*****************************************

Reply via email to