On 12/20/07, Joost Behrends <webmaster@h-labahn.de> wrote:
The syntax with the block in
"newtype State s a = State { runState :: s -> (a,s) }"
is not in the tutorials i read.
 
newtype creates a new type which is treated exactly the same as an existing type at runtime, but which is distinct to the typechecker.
 
For example, this code:
> newtype X = MkX [Int]
> -- MkX :: [Int] -> X
> unX :: X -> [Int]
> unX (MkX val) = val
 
Now, you cannot call "sum (MkX [1,2,3])" because sum takes a list and you're passing an "X".  But you can call "sum (unX (MkX [1,2,3]))".  Since this is a newtype, the work done in "unX" and "MkX" is entirely erased at runtime; no allocation or pointer-following takes place.
 
The syntax given is slightly more complicated:
 
> newtype State s a = State { runState :: s -> (a,s) }
 
This is using the "record" syntax for data constructors, but it's basically the same as the following:
 
> newtype State s a = State (s -> (a,s))
> runState (State f) = f
 
So, runState is just unwrapping the function from the newtype.  Since this is a newtype, there's no actual pointer traversal taking place; the distinction is only made during typechecking.
 
The following two functions should compile to exactly the same machine code:
 
> test1 :: Int -> ((), Int)
> test1 = \x -> ((), x+1)
 
 
> test2 :: Int -> ((), Int)
> test2 = runState (State (\x -> ((), x+1)))
 
 And i do not understand
" ... passed the DivIter directly along ". "Passed along" ??
 
Recall your original code:
 
> divisions :: State DivIter DivIter
> divisions = do
>    y <- get
>    if divisor y <= bound y then do
>        put ( divstep y )
>        divisions
>        else
>            return y
 
Lets de-sugar that:
 
> divisions = get >>= \y -> 
>     if divisor y <= bound y
>        then (put (divstep y) >> divisions)
>        else return y
 
Inlining get, put, and return:
 
> divisions = (State (\s -> (s,s))) >>= \y ->
>     if divisor y <= bound y
>        then (State (\s -> ((), divstep y)) >> divisions)
>        else State (\s -> (y, s))
 
After inlining (>>=) and (>>), and running a few simplification passes (in particular, runState (State x) = x, and beta-reduction), you end up with this:
 
> divisions = State (\y -> 
>    if divisor y <= bound y
>       then runState divisions (divstep y)
>       else (y,y))
 
You can remove the State monad from this pretty trivially:
 
> divisions :: DivIter -> (DivIter, DivIter)
> divisions y =
>    if divisor y <= bound y
>       then divisions (divstep y)
>       else (y,y)
 
or,
 
> divisions y
>   | divisor y <= bound y = divisions (divstep y)
>   | otherwise = (y,y)
 
This version of the code threads the "DivIter" state manually through each call, but it's exactly the same as what the State version is doing.  No destructive updates anywhere to be seen!
 
  -- ryan