Skip to content

Instantly share code, notes, and snippets.

@JordanMartinez
Last active July 4, 2021 00:46
Show Gist options
  • Save JordanMartinez/ae3abb190145838cffbe4a256ac0d123 to your computer and use it in GitHub Desktop.
Save JordanMartinez/ae3abb190145838cffbe4a256ac0d123 to your computer and use it in GitHub Desktop.
Writing Stack-Safe Code - Part 1
module Main where
import Prelude
import Data.List (range, length)
import Data.List.Types (List(..), (:))
import Data.Either (Either(..))
import Effect (Effect)
import Effect.Console (log)
import TryPureScript as TryPureScript
main :: Effect Unit
main = TryPureScript.render =<< TryPureScript.withConsole do
log $ append "safe version: " $ show $ length $ mapLastElemFirst_safe show bigList
-- This has to be run after the safe version. Otherwise, the safe version
-- won't run due to the stack overflow
log $ append "unsafe version: " $ show $ length $ mapLastElemFirst_unsafe show bigList
bigList :: List Int
bigList = range 1 100_000
mapLastElemFirst_unsafe :: forall a b. (a -> b) -> List a -> List b
mapLastElemFirst_unsafe f = case _ of
Nil -> Nil
Cons h tail -> Cons (f h) (mapLastElemFirst_unsafe f tail)
mapLastElemFirst_safe :: forall a b. (a -> b) -> List a -> List b
mapLastElemFirst_safe f ls = go Nil (Left ls)
where
-- To keep track of "where" we are in the data structure, we'll
-- maintain our own stack of what else still needs to be done.
--
-- `Left` values represent items in the tree we haven't yet examined
-- and/or changed.
-- `Right` values represent either the final list or the current state
-- of the final list as we are constructing it.
go :: List a
-> Either (List a) (List b)
-> List b
go stack = case _ of
Left (Cons h tail) ->
-- we've hit the next element in the list
-- remember, we can't modify the value of type `a`
-- represented by `h` by calling `f h` because
-- this might not be the last element.
go (h : stack) (Left tail)
Left Nil ->
-- we've hit the end of the list
-- we can now start consuming the stack we've created
go stack $ Right Nil
Right val ->
-- `val` is either the final list or a portion of that final list
-- because we're still constructing it.
case stack of
-- `a` is the element next closest to the end of the original list.
-- We've already changed all elements after it
-- so we can now map it's type from `a` to `b`.
Cons a rest -> do
let b = f a
go rest $ Right (b : val)
-- the stack is now empty; there's no more elements to map.
-- So, we return the final value
Nil -> val
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment