[Haskell-cafe] Reader monad, refactoring and missing the point all at once

2012-05-02 Thread Eugene Dzhurinsky
Hi all!

Last day I was trying to fix idiii library, because it uses utf8 for parsing
non-unicode content. I found the functions

 -- | Parses one value and returns it as a 'String'
 parseString :: CharEncoding - TagParser String
 parseString enc = do
 v - case enc of
   0x01 - parseUntilWord16Null -- UTF-16
   0x02 - parseUntilWord16Null -- UTF-16 BOM
   _- parseUntilWord8Null  -- ISO-8859-1 or UTF-8
 return $ encPack enc v
 
 encPack :: CharEncoding - [Token] - String
 encPack 0x00s  = Text.unpack $ decodeASCII   $ BS.pack s
 encPack 0x01 (0xFF:0xFE:s) = Text.unpack $ decodeUtf16LE $ BS.pack s
 encPack 0x01 (0xFE:0xFF:s) = Text.unpack $ decodeUtf16BE $ BS.pack s
 encPack 0x02s  = Text.unpack $ decodeUtf16BE $ BS.pack s
 encPack _   s  = Text.unpack $ decodeUtf8$ BS.pack s

updated the dependency from 
 import Data.Text.Encoding (decodeASCII, decodeUtf16LE, decodeUtf16BE, 
 decodeUtf8)
to
 import Data.Text.ICU.Convert

and added implementation for decoding functions:

 decodeAny :: String - BS.ByteString - Text.Text
 decodeAny charset src = unsafePerformIO $ ((flip toUnicode) src) `fmap` open 
 charset (Just True)

 decodeASCII :: BS.ByteString - Text.Text
 decodeASCII = decodeAny latin1
 
 decodeUtf16LE = decodeAny utf-16le
 
 decodeUtf16BE = decodeAny utf-16be
 
 decodeUtf8 = decodeAny utf-8

Now I want to add possibility to specify encoding to yse with decodeASCII. I 
was 
thinking of adding Reader monad and providing some sort of charset
configuration there - but it will lead up to complicating the code, which uses
this parseString function. And this code is used inside Parser of 
Text.ParserCombinators.Poly.State - 
so I will need to update all usages of this parser.

Another approach might be to use IORef with encoding stored there, but I
don't really like this solution.

What would be the best way of refactoring of such kind?

Thanks!

-- 
Eugene N Dzhurinsky


pgp9sNFLGUKtm.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Reader monad wrapping State monad

2011-02-03 Thread michael rice
Given the first program, it seems that the unchanging first element of the 
tuple could be handled by a Reader monad, leading to the second program, where 
b becomes the state, but how do I get the constant a from the Reader monad?

Michael 

==

import Control.Monad.State

type GeneratorState = State (Double,Double)

sqrtST :: GeneratorState Double
sqrtST = do (a,b0) - get
    let b1 = (b0**2.0+a)/(2.0*b0)
    (if (abs (a-b1**2.0))  0.01
  then
    return b1
  else do
    put (a,b1)
    sqrtST)

mySqrt a = let b = a/2.0
   in fst ( runState sqrtST (a,b) )

{-
*Main mySqrt 2.0
1.4142135623746899
-}

==

import Control.Monad.Reader
import Control.Monad.State

type GeneratorState = State Double

sqrtST :: GeneratorState Double
sqrtST = do b0 - get
    let a = ?
    b1 = (b0**2.0+a)/(2.0*b0)
    (if (abs (a-b1**2.0))  0.01
  then
    return b1
  else do
    put b1
    sqrtST)


mySqrt a = let b = a/2.0
   in runReaderT (runState sqrtST b) a




  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad wrapping State monad

2011-02-03 Thread Thomas Davie
Is the idea here merely an exercise in using the state monad?  This can be 
easily performed using pure code.

Bob

On 3 Feb 2011, at 19:18, michael rice wrote:

 Given the first program, it seems that the unchanging first element of the 
 tuple could be handled by a Reader monad, leading to the second program, 
 where b becomes the state, but how do I get the constant a from the Reader 
 monad?
 
 Michael 
 
 ==
 
 import Control.Monad.State
 
 type GeneratorState = State (Double,Double)
 
 sqrtST :: GeneratorState Double
 sqrtST = do (a,b0) - get
 let b1 = (b0**2.0+a)/(2.0*b0)
 (if (abs (a-b1**2.0))  0.01
   then
 return b1
   else do
 put (a,b1)
 sqrtST)
 
 mySqrt a = let b = a/2.0
in fst ( runState sqrtST (a,b) )
 
 {-
 *Main mySqrt 2.0
 1.4142135623746899
 -}
 
 ==
 
 import Control.Monad.Reader
 import Control.Monad.State
 
 type GeneratorState = State Double
 
 sqrtST :: GeneratorState Double
 sqrtST = do b0 - get
 let a = ?
 b1 = (b0**2.0+a)/(2.0*b0)
 (if (abs (a-b1**2.0))  0.01
   then
 return b1
   else do
 put b1
 sqrtST)
 
 
 mySqrt a = let b = a/2.0
in runReaderT (runState sqrtST b) a
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad wrapping State monad

2011-02-03 Thread Daniel Fischer
On Thursday 03 February 2011 20:18:43, michael rice wrote:
 Given the first program, it seems that the unchanging first element of
 the tuple could be handled by a Reader monad, leading to the second
 program, where b becomes the state, but how do I get the constant a from
 the Reader monad?

You need a monad-transformer to use both, Reader and State.
You can use either

ReaderT Double (State Double)

or

StateT Double (Reader Double)

(they're isomorphic).

Then you can query the modifiable state with get (from the MonadState 
class) and the immutable with ask (from the MonadReader class)

type Heron = StateT Double (Reader Double)

sqrtH :: Heron Double
sqrtH = do
  a - ask
  b - get
  let c = 0.5*(b + a/b)
  if (good enough)
then return c
else put c  sqrtH

mySqrt a = runReader (evalStateT sqrtH (a*0.5)) a


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad wrapping State monad

2011-02-03 Thread Ozgur Akgun
On 3 February 2011 19:18, michael rice nowg...@yahoo.com wrote:

 but how do I get the constant a from the Reader monad?


http://hackage.haskell.org/packages/archive/transformers/latest/doc/html/Control-Monad-Trans-Reader.html#v:ask

You also need to change the type to use ReaderT.

-- 
Ozgur Akgun
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad wrapping State monad

2011-02-03 Thread michael rice
Hi Daniel,

Ok, but what I was looking for was ReaderT on top, State on the bottom. This is 
very confusing material, with no apparent conceptual commonality (ad hoc comes 
to mind) among the many examples I've looked at. Sometimes lift is used, other 
times a lift helper function, and in this case no use of lift at all.

Michael

--- On Thu, 2/3/11, Daniel Fischer daniel.is.fisc...@googlemail.com wrote:

From: Daniel Fischer daniel.is.fisc...@googlemail.com
Subject: Re: [Haskell-cafe] Reader monad wrapping State monad
To: haskell-cafe@haskell.org
Cc: michael rice nowg...@yahoo.com
Date: Thursday, February 3, 2011, 2:54 PM

On Thursday 03 February 2011 20:18:43, michael rice wrote:
 Given the first program, it seems that the unchanging first element of
 the tuple could be handled by a Reader monad, leading to the second
 program, where b becomes the state, but how do I get the constant a from
 the Reader monad?

You need a monad-transformer to use both, Reader and State.
You can use either

ReaderT Double (State Double)

or

StateT Double (Reader Double)

(they're isomorphic).

Then you can query the modifiable state with get (from the MonadState 
class) and the immutable with ask (from the MonadReader class)

type Heron = StateT Double (Reader Double)

sqrtH :: Heron Double
sqrtH = do
  a - ask
  b - get
  let c = 0.5*(b + a/b)
  if (good enough)
    then return c
    else put c  sqrtH

mySqrt a = runReader (evalStateT sqrtH (a*0.5)) a




  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad wrapping State monad

2011-02-03 Thread Daniel Fischer
On Thursday 03 February 2011 21:40:13, michael rice wrote:
 Hi Daniel,

 Ok, but what I was looking for was ReaderT on top, State on the bottom.

No problem, just change the definition of the Heron type synonym and swap 
the applcations of runReader[T] and evalState[T] in mySqrt, the monadic 
sqrtH can remain unchanged :)

 This is very confusing material, with no apparent conceptual commonality
 (ad hoc comes to mind) among the many examples I've looked at. Sometimes
 lift is used, other times a lift helper function, and in this case no
 use of lift at all.

That's because only methods of the MonadState and the MonadReader class are 
used and instances of MonadState are propagated/lifted through ReaderT, 
instance of MonadReader are propagated/lifted through StateT.

(
instance MonadReader r m = MonadReader r (StateT s m) where
ask = lift ask
local = ...
instance MonadState s m = MonadState (ReaderT r m) where
get = lift get
put = ...
)

If you use a function on the inner monad which is not propagated to the 
entire transformer stack via class instances, you have to use lift (if you 
have a MonadTrans instance) or something similar.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad wrapping State monad

2011-02-03 Thread michael rice
And swap the arguments.



Thanks for going the extra mile.



Michael


--- On Thu, 2/3/11, Daniel Fischer daniel.is.fisc...@googlemail.com wrote:

From: Daniel Fischer daniel.is.fisc...@googlemail.com
Subject: Re: [Haskell-cafe] Reader monad wrapping State monad
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Thursday, February 3, 2011, 4:15 PM

On Thursday 03 February 2011 21:40:13, michael rice wrote:
 Hi Daniel,

 Ok, but what I was looking for was ReaderT on top, State on the bottom.

No problem, just change the definition of the Heron type synonym and swap 
the applcations of runReader[T] and evalState[T] in mySqrt, the monadic 
sqrtH can remain unchanged :)

 This is very confusing material, with no apparent conceptual commonality
 (ad hoc comes to mind) among the many examples I've looked at. Sometimes
 lift is used, other times a lift helper function, and in this case no
 use of lift at all.

That's because only methods of the MonadState and the MonadReader class are 
used and instances of MonadState are propagated/lifted through ReaderT, 
instance of MonadReader are propagated/lifted through StateT.

(
instance MonadReader r m = MonadReader r (StateT s m) where
    ask = lift ask
    local = ...
instance MonadState s m = MonadState (ReaderT r m) where
    get = lift get
    put = ...
)

If you use a function on the inner monad which is not propagated to the 
entire transformer stack via class instances, you have to use lift (if you 
have a MonadTrans instance) or something similar.




  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Reader monad

2010-12-29 Thread michael rice
From: Control.Monad.Reader
type Reader r = ReaderT r IdentityThe parameterizable reader monad.
Computations are functions of a shared environment.
The return function ignores the environment, while = passes
 the inherited environment to both subcomputations 


Is there an unparameterizable reader monad?
Michael



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad

2010-12-29 Thread Ryan Ingram
On Wed, Dec 29, 2010 at 8:06 AM, michael rice nowg...@yahoo.com wrote:
 Is there an unparameterizable reader monad?

I'm not sure this is the answer you are looking for, but it seems like the
obvious one.

Pick an r, say String.  Now  Reader String is an unparameterizable
reader monad that passes around a String.

  -- ryan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad

2010-12-29 Thread michael rice
Hi, Ryan.

Since I'm trying to understand Reader, I wanted to be aware of all cases of 
Reader.  

==

From the docs (and tuts) newtype creates a new type out of an existing type
and gives a single constructor for doing so.


From: http://www.haskell.org/tutorial/moretypes.html 

  newtype Natural = MakeNatural Integer

  This creates an entirely new type, Natural, whose only constructor contains
  a single Integer. The constructor MakeNatural converts between an Natural and
  an Integer:

toNatural   :: Integer - Natural
toNatural x | x  0 = error Can't create negative naturals! 
    | otherwise = MakeNatural x

fromNatural :: Natural - Integer
fromNatural (MakeNatural i) = i


In the above case the existing type is Integer. The new type behaves like the 
existing type, but we can pattern match with the new type.

++

In the case of ReaderT and StateT

newtype ReaderT r m a = ReaderT {
    -- | The underlying computation, as a function of the environment.
    runReaderT :: r - m a
    }

newtype StateT s m a = StateT { runStateT :: s - m (a, s) }

what is the existing type?

Michael

--- On Wed, 12/29/10, Ryan Ingram ryani.s...@gmail.com wrote:

From: Ryan Ingram ryani.s...@gmail.com
Subject: Re: [Haskell-cafe] Reader monad
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Wednesday, December 29, 2010, 11:11 AM

On Wed, Dec 29, 2010 at 8:06 AM, michael rice nowg...@yahoo.com wrote:
 Is there an unparameterizable reader monad?

I'm not sure this is the answer you are looking for, but it seems like the 
obvious one.


Pick an r, say String.  Now  Reader String is an unparameterizable reader 
monad that passes around a String.

  -- ryan




  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad

2010-12-29 Thread Henning Thielemann


On Wed, 29 Dec 2010, michael rice wrote:


In the case of ReaderT and StateT

newtype ReaderT r m a = ReaderT {
    -- | The underlying computation, as a function of the environment.
    runReaderT :: r - m a
    }

newtype StateT s m a = StateT { runStateT :: s - m (a, s) }

what is the existing type?



The existing type is 'r - m a'. You could also write


newtype ReaderT r m a = ReaderT (r - m a)


This would be the same type as above, but it would have no accessor 
function 'runReaderT'.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad

2010-12-29 Thread Michael Lazarev
2010/12/29 michael rice nowg...@yahoo.com

 From the docs (and tuts) newtype creates a new type out of an existing
type
 and gives a single constructor for doing so.

 what is the existing type?


Michael, you may want to see this section:
http://learnyouahaskell.com/functors-applicative-functors-and-monoids#the-newtype-keyword
and also section titled type vs. newtype vs. data below. It has good
explanation why there is
at least three keywords in Haskell to define types, and which of them do
what. And how they do it.

From my experience, this book in a whole could be useful to you. It also has
explanation how Reader
is constructed step-by-step.

As far as I know, there has been code for Reader monad in Haskell Wiki.
Unfortunately,
after it has been migrated, page not found error has become not very
uncommon on it, and
either i was not able to found it, or it really is missing.

Out of practical considerations, library authors decided to define more
complicated ReaderT monad transformer,
because it can be made to behave as Reader if the former wraps Identity
monad.

Hope this helps.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad

2010-12-29 Thread michael rice
I think of (r - m a) as a type signature and Int or Bool by themselves as 
types. So, all type signatures are themselves types?

Michael

--- On Wed, 12/29/10, Henning Thielemann lemm...@henning-thielemann.de wrote:

From: Henning Thielemann lemm...@henning-thielemann.de
Subject: Re: [Haskell-cafe] Reader monad
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Wednesday, December 29, 2010, 12:28 PM


On Wed, 29 Dec 2010, michael rice wrote:

 In the case of ReaderT and StateT
 
 newtype ReaderT r m a = ReaderT {
     -- | The underlying computation, as a function of the environment.
     runReaderT :: r - m a
     }
 
 newtype StateT s m a = StateT { runStateT :: s - m (a, s) }
 
 what is the existing type?


The existing type is 'r - m a'. You could also write

 newtype ReaderT r m a = ReaderT (r - m a)

This would be the same type as above, but it would have no accessor function 
'runReaderT'.




  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad

2010-12-29 Thread Tillmann Rendel

Hi,

Michael Rice wrote:

I think of (r - m a) as a type signature and Int or Bool by themselves
as types. So, all type signatures are themselves types?


Yes.

In Haskell, functions are first class, so function types like (r - m a) 
are themselves types.


  Tillmann

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad

2010-12-29 Thread michael rice
Hi, Michael.

Yes, I'd already noticed that ReaderT preceded Reader. Guess I'll have to check 
out the Indentity monad too. I hope it's not dependent upon yet another monad.  
;-)

Thanks for the link. I go there a lot.

Michael

--- On Wed, 12/29/10, Michael Lazarev lazarev.mich...@gmail.com wrote:

From: Michael Lazarev lazarev.mich...@gmail.com
Subject: Re: [Haskell-cafe] Reader monad
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Wednesday, December 29, 2010, 12:42 PM



2010/12/29 michael rice nowg...@yahoo.com

 From the docs (and tuts) newtype creates a new type out of an existing type
 and gives a single constructor for doing so.


 what is the existing type?


Michael, you may want to see this section:
http://learnyouahaskell.com/functors-applicative-functors-and-monoids#the-newtype-keyword

and also section titled type vs. newtype vs. data below. It has good 
explanation why there is
at least three keywords in Haskell to define types, and which of them do what. 
And how they do it.

From my experience, this book in a whole could be useful to you. It also has 
explanation how Reader

is constructed step-by-step.

As far as I know, there has been code for Reader monad in Haskell Wiki. 
Unfortunately,
after it has been migrated, page not found error has become not very uncommon 
on it, and

either i was not able to found it, or it really is missing.

Out of practical considerations, library authors decided to define more 
complicated ReaderT monad transformer, 
because it can be made to behave as Reader if the former wraps Identity monad.


Hope this helps.





  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad

2010-12-29 Thread Daniel Fischer
On Wednesday 29 December 2010 19:30:11, michael rice wrote:
 Yes, I'd already noticed that ReaderT preceded Reader. Guess I'll have
 to check out the Indentity monad too. I hope it's not dependent upon yet
 another monad. 

No, the Identity monad stands alone.
And as the name suggests, it's pretty simple.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad

2010-12-29 Thread michael rice
Hi, Daniel.

I had an Aha! moment and it all makes sense now. Just as the State monad can 
hold a generator (which can change) and pass it down a calculation chain, a 
Reader monad can hold an environment (which doesn't change) and pass it down a 
calculation chain. I was wondering how I could include a (global) house betting 
limit in that craps application I've been playing with (without passing it as a 
parameter) and it sounds like the Reader monad would be an ideal candidate. 
Correct? It also sounds like a job for monad transforms.

Michael

--- On Wed, 12/29/10, Daniel Fischer daniel.is.fisc...@googlemail.com wrote:

From: Daniel Fischer daniel.is.fisc...@googlemail.com
Subject: Re: [Haskell-cafe] Reader monad
To: haskell-cafe@haskell.org
Cc: michael rice nowg...@yahoo.com
Date: Wednesday, December 29, 2010, 2:47 PM

On Wednesday 29 December 2010 19:30:11, michael rice wrote:
 Yes, I'd already noticed that ReaderT preceded Reader. Guess I'll have
 to check out the Indentity monad too. I hope it's not dependent upon yet
 another monad. 

No, the Identity monad stands alone.
And as the name suggests, it's pretty simple.




  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad

2010-12-29 Thread Albert Y. C. Lai

On 10-12-29 12:50 PM, michael rice wrote:

I think of (r - m a) as a type signature and Int or Bool by themselves
as types. So, all type signatures are themselves types?


http://www.haskell.org/onlinereport/haskell2010/haskellch4.html#x10-620004

In particular

gendecl → vars :: [context =] type(type signature)

Therefore I think of

n :: Int
f :: r - m a

as type signatures, and their right-hand sides alone,

Int
r - m a

as types.

I also include the context = part in my types, for example

m :: Num a = a

I take the type to be

Num a = a

The grammar splits out the context = part just for the sake of reuse 
in other places such as


topdecl → ...
| data [context =] simpletype [= constrs] [deriving]


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad

2010-12-29 Thread Michael Lazarev
2010/12/29 Albert Y. C. Lai tre...@vex.net

 On 10-12-29 12:50 PM, michael rice wrote:

 I think of (r - m a) as a type signature and Int or Bool by themselves
 as types. So, all type signatures are themselves types?


 http://www.haskell.org/onlinereport/haskell2010/haskellch4.html#x10-620004

 In particular

 gendecl → vars :: [context =] type(type signature)

 Therefore I think of

 n :: Int
 f :: r - m a

 as type signatures, and their right-hand sides alone,

 Int
 r - m a

 as types.


I used to think about types as mathematical sets, and type signatures in
this case are just sequences of characters denoting these types. They of
course must have some formal grammar as it was quoted above.

I'd like to note that one type can be denoted by many type signatures. For
example, String and [Char]. And as another case, a - b and c - d. One may
come up with more advanced examples involving type families.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad

2010-12-29 Thread Michael Lazarev
2010/12/29 michael rice nowg...@yahoo.com
 I had an Aha! moment and it all makes sense now. Just as the State monad 
 can hold a generator (which can change) and pass it down a calculation chain, 
 a Reader monad can hold an environment (which doesn't change) and pass it 
 down a calculation chain. I was wondering how I could include a (global) 
 house betting limit in that craps application I've been playing with (without 
 passing it as a parameter) and it sounds like the Reader monad would be an 
 ideal candidate. Correct? It also sounds like a job for monad transforms.

That is right. You need transformers if you want to have one value as
settings to read, other value as a state, and so on, and they must be
simultaneously accessible in some function. Or, for example, if you
want to build a sequence of IO actions by functions that share the
same environment.

After you said that you had an Aha! moment, I remembered how I had
something alike not very long ago. That was surprising event when I
ended up with some transformer stack written myself although just
several minutes ago I would consider this to be some dark wizardry.

When I was dealing with monads for the first time, I tried reading
source code and explanations. Soon I found that pure unapplied theory
was making such a dismal, depressing feeling on me that I was not able
to continue.

But some time after I was writing an application in Haskell. It was
real, and contrary to my previous theoretical studies the process was
much fun. I had good FP background at that time, and had no problem
writing everything in functional style. Since everything that can be
done with monads can also be done without them, I didn't use any monad
except IO (in main function :) ). Not that I especially avoided them,
I just didn't think about them.

And then I noticed that I constantly pass one same parameter to a lot
of functions. And then -- since I remembered the boring theory -- bam!
-- I introduced Reader into the code. And it worked. Which tempted me
to interweave Reader and Writer, and so on, and twenty minutes later I
had monstrosity that I only saw before in others' code: ReaderT
WriterT State  and so on :)

So, good luck with your application!

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad

2010-12-29 Thread David Leimbach
On Wed, Dec 29, 2010 at 1:48 PM, Michael Lazarev
lazarev.mich...@gmail.comwrote:

 2010/12/29 michael rice nowg...@yahoo.com
  I had an Aha! moment and it all makes sense now. Just as the State
 monad can hold a generator (which can change) and pass it down a calculation
 chain, a Reader monad can hold an environment (which doesn't change) and
 pass it down a calculation chain. I was wondering how I could include a
 (global) house betting limit in that craps application I've been playing
 with (without passing it as a parameter) and it sounds like the Reader monad
 would be an ideal candidate. Correct? It also sounds like a job for monad
 transforms.

 That is right. You need transformers if you want to have one value as
 settings to read, other value as a state, and so on, and they must be
 simultaneously accessible in some function. Or, for example, if you
 want to build a sequence of IO actions by functions that share the
 same environment.

 After you said that you had an Aha! moment, I remembered how I had
 something alike not very long ago. That was surprising event when I
 ended up with some transformer stack written myself although just
 several minutes ago I would consider this to be some dark wizardry.

 When I was dealing with monads for the first time, I tried reading
 source code and explanations. Soon I found that pure unapplied theory
 was making such a dismal, depressing feeling on me that I was not able
 to continue.

 But some time after I was writing an application in Haskell. It was
 real, and contrary to my previous theoretical studies the process was
 much fun. I had good FP background at that time, and had no problem
 writing everything in functional style. Since everything that can be
 done with monads can also be done without them, I didn't use any monad
 except IO (in main function :) ). Not that I especially avoided them,
 I just didn't think about them.

 And then I noticed that I constantly pass one same parameter to a lot
 of functions. And then -- since I remembered the boring theory -- bam!
 -- I introduced Reader into the code. And it worked. Which tempted me
 to interweave Reader and Writer, and so on, and twenty minutes later I
 had monstrosity that I only saw before in others' code: ReaderT
 WriterT State  and so on :)


Reader Writer State is commonly needed in big applications so transformers
provides one for us:

http://hackage.haskell.org/packages/archive/transformers/0.2.2.0/doc/html/Control-Monad-Trans-RWS-Lazy.html

Pretty cool stuff if you ask me.  I often wondered about the correct
stacking order of Monad transformers, or how often it mattered.

Dave



 So, good luck with your application!

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad

2010-12-29 Thread Michael Lazarev
2010/12/30 David Leimbach leim...@gmail.com:

 Reader Writer State is commonly needed in big applications so transformers
 provides one for us:
 http://hackage.haskell.org/packages/archive/transformers/0.2.2.0/doc/html/Control-Monad-Trans-RWS-Lazy.html
 Pretty cool stuff if you ask me.  I often wondered about the correct
 stacking order of Monad transformers, or how often it mattered.

Thanks, it is very cool indeed!
And it turns out that it's not simply kind of the type RWST r w s m a
= ReaderT r WriterT w StateT s m a,
it has completely independent implementation. It is done in one layer,
so no lifts for tell, get, put, modify and so on.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-24 Thread Henning Thielemann


On Fri, 22 Aug 2008, Alexander Dunlap wrote:


You can always change how you unsafePerformIO the data, though. If you
want to set Planck's constant to 42 (or whatever), just change the
unsafePerformIO $ whatever to unsafePerformIO $ return 42.


you can't change it at runtime

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-22 Thread Alexander Dunlap
On Wed, Aug 20, 2008 at 1:49 AM, Henning Thielemann
[EMAIL PROTECTED] wrote:

 On Mon, 18 Aug 2008, [EMAIL PROTECTED] wrote:

 G'day all.

 Quoting Bjorn Buckwalter [EMAIL PROTECTED]:

 I'd store the constants in a data structure along the lines of:

 data AstroData a = AstroData
  { mu_Earth:: GravitationalParameter a
  , leapSeconds :: LeapSecondTable
  }

 I would like to know if there is any consensus on what is the best way
 to make such a data structure accessible in pure functions. Passing it
 explicitly would be a mess.

 In this situation, there isn't necessarily any shame in using a
 top-level unsafePerformIO as long as it's well-hidden:

  module AstroData (AstroData(..), globalAstroData) where

  data AstroData = AstroData Int

 But here my argument about playing around with the Planck constant becomes
 relevant.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


You can always change how you unsafePerformIO the data, though. If you
want to set Planck's constant to 42 (or whatever), just change the
unsafePerformIO $ whatever to unsafePerformIO $ return 42.

Alex
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-20 Thread Henning Thielemann


On Mon, 18 Aug 2008, [EMAIL PROTECTED] wrote:


G'day all.

Quoting Bjorn Buckwalter [EMAIL PROTECTED]:


I'd store the constants in a data structure along the lines of:


data AstroData a = AstroData
 { mu_Earth:: GravitationalParameter a
 , leapSeconds :: LeapSecondTable
 }


I would like to know if there is any consensus on what is the best way
to make such a data structure accessible in pure functions. Passing it
explicitly would be a mess.


In this situation, there isn't necessarily any shame in using a
top-level unsafePerformIO as long as it's well-hidden:

  module AstroData (AstroData(..), globalAstroData) where

  data AstroData = AstroData Int


But here my argument about playing around with the Planck constant becomes 
relevant.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-18 Thread Bjorn Buckwalter
All,

I have a growing amount of astrodynamics code that relies on various
physical constants. The problem with these so called constants are
that they either aren't really constants or aren't well known. An
example is the leap second table (see Data.Time.Clock.TAI). I'd like
to be able to fetch current values of these constants at runtime and
make them accessible to my astrodynamics functions by some means. To
clarify, once initialized the constants will be considered constant
for the remainder of the program.

I'd store the constants in a data structure along the lines of:

 data AstroData a = AstroData
   { mu_Earth:: GravitationalParameter a
   , leapSeconds :: LeapSecondTable
   }

I would like to know if there is any consensus on what is the best way
to make such a data structure accessible in pure functions. Passing it
explicitly would be a mess. It seems that two options are to use
either a Reader monad or implicit parameters. Using a Reader monad is
straight forward enough though it requires writing/converting code
in/to monadic style and adds some clutter to the formulae. It seems
implicit parameters could be cleaner but I've seen them referred to as
everything from evil to just what you need and rendering the Reader
monad obsolete...

What do you people recommend?

Thanks,
Bjorn Buckwalter
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-18 Thread Bjorn Buckwalter
All,

I have a growing amount of astrodynamics code that relies on various
physical constants. The problem with these so called constants are
that they either aren't really constants or aren't well known. An
example is the leap second table (see Data.Time.Clock.TAI). I'd like
to be able to fetch current values of these constants at runtime and
make them accessible to my astrodynamics functions by some means. To
clarify, once initialized the constants will be considered constant
for the remainder of the program.

I'd store the constants in a data structure along the lines of:

 data AstroData a = AstroData
   { mu_Earth:: GravitationalParameter a
   , leapSeconds :: LeapSecondTable
   }

I would like to know if there is any consensus on what is the best way
to make such a data structure accessible in pure functions. Passing it
explicitly would be a mess. It seems that two options are to use
either a Reader monad or implicit parameters. Using a Reader monad is
straight forward enough though it requires writing/converting code
in/to monadic style and adds some clutter to the formulae. It seems
implicit parameters could be cleaner but I've seen them referred to as
everything from evil to just what you need and rendering the Reader
monad obsolete...

What do you people recommend?

Thanks,
Bjorn Buckwalter
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-18 Thread Henning Thielemann


On Mon, 18 Aug 2008, Bjorn Buckwalter wrote:


I would like to know if there is any consensus on what is the best way
to make such a data structure accessible in pure functions. Passing it
explicitly would be a mess. It seems that two options are to use
either a Reader monad or implicit parameters. Using a Reader monad is
straight forward enough though it requires writing/converting code
in/to monadic style and adds some clutter to the formulae. It seems
implicit parameters could be cleaner but I've seen them referred to as
everything from evil to just what you need and rendering the Reader
monad obsolete...


I expect that you will get the same range of opinions as you got from your 
search. As far as I know implicit parameters break referential 
transparency.

  
http://www.haskell.org/haskellwiki/The_Monad.Reader/Issue2/FunWithLinearImplicitParameters
 So I prefer Reader monad. The burden of converting to monadic style pays 
off when you need to use the same code with different values for the 
constants. (E.g. find out for which value of the Planck constant the 
universe collapses and for which it oscillates etc. :-)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-18 Thread Brandon S. Allbery KF8NH

On 2008 Aug 18, at 11:16, Henning Thielemann wrote:

know implicit parameters break referential transparency.
 
http://www.haskell.org/haskellwiki/The_Monad.Reader/Issue2/FunWithLinearImplicitParameters


Are you making the same mistake I did?  Linear implicit parameters are  
different from implicit parameters.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-18 Thread Henning Thielemann


On Mon, 18 Aug 2008, Brandon S. Allbery KF8NH wrote:


On 2008 Aug 18, at 11:16, Henning Thielemann wrote:

know implicit parameters break referential transparency.
http://www.haskell.org/haskellwiki/The_Monad.Reader/Issue2/FunWithLinearImplicitParameters


Are you making the same mistake I did?  Linear implicit parameters are 
different from implicit parameters.


I haven't look into the details, so I certainly make any possible mistake.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-18 Thread Henning Thielemann


On Mon, 18 Aug 2008, Bjorn Buckwalter wrote:


On Mon, Aug 18, 2008 at 11:16 AM, Henning Thielemann
[EMAIL PROTECTED] wrote:


On Mon, 18 Aug 2008, Bjorn Buckwalter wrote:


I would like to know if there is any consensus on what is the best way
to make such a data structure accessible in pure functions. Passing it
explicitly would be a mess. It seems that two options are to use
either a Reader monad or implicit parameters. Using a Reader monad is
straight forward enough though it requires writing/converting code
in/to monadic style and adds some clutter to the formulae. It seems
implicit parameters could be cleaner but I've seen them referred to as
everything from evil to just what you need and rendering the Reader
monad obsolete...


I expect that you will get the same range of opinions as you got from your
search. As far as I know implicit parameters break referential transparency.
 
http://www.haskell.org/haskellwiki/The_Monad.Reader/Issue2/FunWithLinearImplicitParameters
 So I prefer Reader monad. The burden of converting to monadic style pays
off when you need to use the same code with different values for the
constants. (E.g. find out for which value of the Planck constant the
universe collapses and for which it oscillates etc. :-)


Love the example but could you elaborate a little on how monadic style
helps with this? (This is probably a matter of it not being obvious to
me what approach you would take to solving the problem.)


Instead of
  muEarth :: GravitationalParameter a
  muEarth = ???

  escapeVelocity :: a
  escapeVelocity = ... muEarth ...

you would write

  data AstroData a = AstroData
{ muEarth :: GravitationalParameter a
, leapSeconds :: LeapSecondTable
}

  escapeVelocity :: Reader (AstroData a) a
  escapeVelocity =
 do mu - asks muEarth
return (... mu ...)

Even better you would introduce a newtype for Reader (AstroData a). This 
way you can add any monadic functionality later (Writer et.al.).

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Fwd: [Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-18 Thread Bjorn Buckwalter
On Mon, Aug 18, 2008 at 2:02 PM, Henning Thielemann
[EMAIL PROTECTED] wrote:

 On Mon, 18 Aug 2008, Bjorn Buckwalter wrote:

 On Mon, Aug 18, 2008 at 11:16 AM, Henning Thielemann
 [EMAIL PROTECTED] wrote:

 On Mon, 18 Aug 2008, Bjorn Buckwalter wrote:

 I would like to know if there is any consensus on what is the best way
 to make such a data structure accessible in pure functions. Passing it
 explicitly would be a mess. It seems that two options are to use
 either a Reader monad or implicit parameters. Using a Reader monad is
 straight forward enough though it requires writing/converting code
 in/to monadic style and adds some clutter to the formulae. It seems
 implicit parameters could be cleaner but I've seen them referred to as
 everything from evil to just what you need and rendering the Reader
 monad obsolete...

 I expect that you will get the same range of opinions as you got from
 your
 search. As far as I know implicit parameters break referential
 transparency.

  
 http://www.haskell.org/haskellwiki/The_Monad.Reader/Issue2/FunWithLinearImplicitParameters
  So I prefer Reader monad. The burden of converting to monadic style pays
 off when you need to use the same code with different values for the
 constants. (E.g. find out for which value of the Planck constant the
 universe collapses and for which it oscillates etc. :-)

 Love the example but could you elaborate a little on how monadic style
 helps with this? (This is probably a matter of it not being obvious to
 me what approach you would take to solving the problem.)

 Instead of
  muEarth :: GravitationalParameter a
  muEarth = ???

  escapeVelocity :: a
  escapeVelocity = ... muEarth ...

 you would write

  data AstroData a = AstroData
{ muEarth :: GravitationalParameter a
, leapSeconds :: LeapSecondTable
}

  escapeVelocity :: Reader (AstroData a) a
  escapeVelocity =
 do mu - asks muEarth
return (... mu ...)

 Even better you would introduce a newtype for Reader (AstroData a). This way
 you can add any monadic functionality later (Writer et.al.).

Right, and I'd evaluate it using e.g.:

 runReader escapeVelocity myAstroData

But with implicit params I suppose I'd define (untested) e.g.:

 escapeVelocity :: (?astro :: AstroData a) = a
 escapeVelocity = ... mu ... where mu = muEarth ?astro

To evaluate this I'd use:

 let ?astro = myAstroData in escapeVelocity

Which is comparable to the Reader version (with the
advantage/disadvantage of the body of 'escapeVelocity' not being
monadic).

In retrospect I think I misunderstood what you were saying in you
first email. I thought you were arguing that the monadic style would
have an advantage over implicit params in the Planck problem. But you
probably only meant to reemphasize the advantage (of either solution)
over hard-coding constants...

Thanks again, your Reader example is virtually identical to what I
started off with so at least I know I'm not completely off target for
a monadic implementation.

(Sorry about the reposts Henning, I keep forgetting to cc the café!)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Fwd: [Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-18 Thread Henning Thielemann

Bjorn Buckwalter schrieb:

On Mon, Aug 18, 2008 at 2:02 PM, Henning Thielemann

[EMAIL PROTECTED] wrote:



Instead of
 muEarth :: GravitationalParameter a
 muEarth = ???

 escapeVelocity :: a
 escapeVelocity = ... muEarth ...

you would write

 data AstroData a = AstroData
   { muEarth :: GravitationalParameter a
   , leapSeconds :: LeapSecondTable
   }

 escapeVelocity :: Reader (AstroData a) a
 escapeVelocity =
do mu - asks muEarth
   return (... mu ...)

Even better you would introduce a newtype for Reader (AstroData a). This way
you can add any monadic functionality later (Writer et.al.).


Right, and I'd evaluate it using e.g.:

 runReader escapeVelocity myAstroData

But with implicit params I suppose I'd define (untested) e.g.:

 escapeVelocity :: (?astro :: AstroData a) = a
 escapeVelocity = ... mu ... where mu = muEarth ?astro

To evaluate this I'd use:

 let ?astro = myAstroData in escapeVelocity

Which is comparable to the Reader version (with the
advantage/disadvantage of the body of 'escapeVelocity' not being
monadic).


In my opinion the implicit parameters don't make things simpler, only 
less portable, that's why I prefer the Reader monad.


 In retrospect I think I misunderstood what you were saying in you
 first email. I thought you were arguing that the monadic style would
 have an advantage over implicit params in the Planck problem. But you
 probably only meant to reemphasize the advantage (of either solution)
 over hard-coding constants...

indeed

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Fwd: [Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-18 Thread Evan Laforge
 Which is comparable to the Reader version (with the
 advantage/disadvantage of the body of 'escapeVelocity' not being
 monadic).

 In my opinion the implicit parameters don't make things simpler, only less
 portable, that's why I prefer the Reader monad.

They also seem to be removed from ghc:

http://www.haskell.org/pipermail/cvs-ghc/2006-September/031824.html

So it would probably be a mistake to write new code using them.

As an aside, if that's really the complete patch I'm impressed how few
lines were involved.  136 lines out of TcSimplify.lhs and misc tiny
changes in other files.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-18 Thread Brandon S. Allbery KF8NH

On 2008 Aug 18, at 16:20, Evan Laforge wrote:

Which is comparable to the Reader version (with the
advantage/disadvantage of the body of 'escapeVelocity' not being
monadic).


In my opinion the implicit parameters don't make things simpler,  
only less

portable, that's why I prefer the Reader monad.


They also seem to be removed from ghc:

http://www.haskell.org/pipermail/cvs-ghc/2006-September/031824.html



Again, that's *linear* implicit parameters (%foo instead of ?foo).

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-18 Thread Evan Laforge
 They also seem to be removed from ghc:

 http://www.haskell.org/pipermail/cvs-ghc/2006-September/031824.html


 Again, that's *linear* implicit parameters (%foo instead of ?foo).

Oh, you're right.  I made exactly the same mistake you made, and right
after you warned against making it too.  I always thought linear was
the ? stuff, but now I see it's not.  Maybe it's best that it's gone
so we only have one flavor of implicit parameters feature from here
on out.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-18 Thread Brandon S. Allbery KF8NH


On 2008 Aug 18, at 17:09, Evan Laforge wrote:


They also seem to be removed from ghc:

http://www.haskell.org/pipermail/cvs-ghc/2006-September/031824.html



Again, that's *linear* implicit parameters (%foo instead of ?foo).


Oh, you're right.  I made exactly the same mistake you made, and right
after you warned against making it too.  I always thought linear was
the ? stuff, but now I see it's not.  Maybe it's best that it's gone
so we only have one flavor of implicit parameters feature from here
on out.


Don't feel too bad; the main reason I'm commenting on it is I managed  
to confuse a bunch of people in public before I was set straight on  
it, so I kinda feel a bit guilty when people are confused by it.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-18 Thread ajb

G'day all.

Quoting Bjorn Buckwalter [EMAIL PROTECTED]:


I'd store the constants in a data structure along the lines of:


data AstroData a = AstroData
  { mu_Earth:: GravitationalParameter a
  , leapSeconds :: LeapSecondTable
  }


I would like to know if there is any consensus on what is the best way
to make such a data structure accessible in pure functions. Passing it
explicitly would be a mess.


In this situation, there isn't necessarily any shame in using a
top-level unsafePerformIO as long as it's well-hidden:

module AstroData (AstroData(..), globalAstroData) where

data AstroData = AstroData Int

-- You really don't want this function inlined.  You also
-- really don't want this function to be polymorphic.
{-# NOINLINE globalAstroData #-}
globalAstroData :: AstroData
globalAstroData = unsafePerformIO $ do
d - return 42-- Or whatever
return (AstroData d)

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-18 Thread Richard A. O'Keefe

Just an idiot-level question: so these constants are subject
to revision, but *how often*?  What is the actual cost of
recompiling and using them *as* constants, compared with the
cost of rereading the stuff every time you run the program and
passing it around?

--
If stupidity were a crime, who'd 'scape hanging?







___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-18 Thread ajb

G'day all.

Quoting Richard A. O'Keefe [EMAIL PROTECTED]:


Just an idiot-level question: so these constants are subject
to revision, but *how often*?


Good question.  For leap seconds:

 - The data can change no quicker than once every 6 months.
 - The shortest time between changes was 6 months, and the longest
   (so far) was 7 years.
 - The mean change is once every 18 months.
 - You get just under 6 months' notice before a change comes into
   effect.  (No more, no less.)

For most programs, it's the last point that concerns me the most...


What is the actual cost of
recompiling and using them *as* constants, compared with the
cost of rereading the stuff every time you run the program and
passing it around?


...because the main cost probably isn't recompiling, it's redeployment.
I don't know about this program in particular, but release cycles longer
than six months are hardly uncommon in our business.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe