module TextUI.ItemField.Operations where import Data.List (elemIndices) import TextUI.ItemField.Types -- | Updates the state of the specified item number to the new state. changeItemState :: ItemState -> ItemField -> Int -> ItemField changeItemState newSt8 field st8idx = let ss = itemst8 field (b,a) = splitAt st8idx ss a' = if null a then [] else tail a in if null ss || st8idx >= length ss then field else field { itemst8 = b ++ (newSt8 : a') } -- | Returns the list of the currently marked items in the field getMarked :: ItemField -> [Int] getMarked = elemIndices Marked . itemst8 -- | groupRange returns a tuple of the first and last indices of items -- in group of which item n is a member. groupRange :: NumItems -> [Items] -> (NumItems, NumItems) groupRange _ [] = (0,0) groupRange n (Items c:ss) = let (b,e) = groupRange (n - c) ss in if c > n then (0,max 0 (c-1)) else (c+b, c+e) groupRange n (ItemGroup _ c:ss) = let gl = cntItems [c] (b,e) = groupRange (n - gl) ss in if gl > n then groupRange n [c] else (gl+b, gl+e) -- | setAllFree Converts the state of all items in the field to Free setAllFree :: ItemField -> ItemField setAllFree field = let num = cntItems $ items field in field { itemst8 = replicate num Free }