Skip to content

Commit

Permalink
style: change all foldl to foldl'
Browse files Browse the repository at this point in the history
(I've just read how unfashionable foldl is and at a glance all the functions
are or should be strict, so changing it to foldr would not make sense.)
  • Loading branch information
Mikolaj committed Mar 9, 2011
1 parent d8f271a commit 5c58cf0
Show file tree
Hide file tree
Showing 4 changed files with 9 additions and 6 deletions.
8 changes: 5 additions & 3 deletions src/Actions.hs
Expand Up @@ -490,9 +490,11 @@ search =
do
Level { lmap = lmap } <- gets slevel
Movable { mloc = ploc } <- gets splayer
let searchTile (Tile (Door hv (Just n)) x,t') = Just (Tile (Door hv (Just (max (n - 1) 0))) x, t')
searchTile t = Just t
slmap = foldl (\ l m -> update searchTile (shift ploc m) l) lmap moves
let searchTile (Tile (Door hv (Just n)) x, t') =
(Tile (Door hv (Just (max (n - 1) 0))) x, t')
searchTile t = t
f l m = M.adjust searchTile (shift ploc m) l
slmap = foldl' f lmap moves
modify (updateLevel (updateLMap (const slmap)))

-- | Start the floor targeting mode or toggle between the two floor modes.
Expand Down
2 changes: 1 addition & 1 deletion src/Item.hs
Expand Up @@ -245,7 +245,7 @@ strongestSword :: [Item] -> Int
strongestSword l =
let aux acc (Item { itype = Sword i }) = max acc i
aux acc _ = acc
in foldl aux 0 l
in foldl' aux 0 l

makeObject :: Int -> (String -> String) -> String -> String
makeObject 1 adj obj = let b = adj obj
Expand Down
3 changes: 2 additions & 1 deletion src/LambdaHack.hs
Expand Up @@ -2,6 +2,7 @@ module Main where

import System.Directory
import Control.Monad
import Data.List as L
import Data.Map as M

import Action
Expand Down Expand Up @@ -79,5 +80,5 @@ generate config session msg =
defState = defaultState player dng lvl
state = defState { sassocs = assocs, sconfig = config }
k = Config.get config "heroes" "extraHeroes"
hstate = foldl (addHero hp) state [1..k]
hstate = foldl' (addHero hp) state [1..k]
handlerToIO session hstate msg handle
2 changes: 1 addition & 1 deletion src/Level.hs
Expand Up @@ -559,7 +559,7 @@ viewSmell n = let k | n > 9 = '*'
-- Scatter randomly or not?
scatterItems :: [Item] -> Loc -> Level -> Level
scatterItems items loc lvl@(Level { lmap = lmap }) =
let joinItems items = foldl (\ acc i -> snd (joinItem i acc)) items
let joinItems items = foldl' (\ acc i -> snd (joinItem i acc)) items
t = lmap `at` loc
nt = t { titems = joinItems items (titems t) }
ntRemember = lmap `rememberAt` loc
Expand Down

0 comments on commit 5c58cf0

Please sign in to comment.