Settings are defined using mapping from text to value. This value can be text or number. \begin{code}
-- | 
-- Maintainer : silva.samuel@alumni.uminho.pt
-- Stability  : experimental
-- Portability: portable
-- This module implements configurations 
module Music.Analysis.Abstract.Settings where
import Music.Analysis.PF (split, p1, p2, grd)
import Music.Analysis.Base (Text, Number)
import Data.Map(Map, empty, lookup, alter, union, fromList, map, unionWith)
--    foldWithKey, filterWithKey)
import Data.Maybe (Maybe(..), maybe)
import Data.Either (Either(..), either)
import Data.Function ((.), id, const, flip)
--import Data.List ((++))
import Data.Bool (Bool(..))
--import Data.Eq (Eq(..))
import Prelude (Double) 
\end{code} Settings is a mapping from keys to values with additional information of keys. This additional information is very helpful to disambiguate merging settings when some settings are more priority than others. \begin{code}
-- | Definition of Settings to make general configurations
-- It is possible grow
type Settings = Map Text (Bool, Either Text Number)
--(Map Text (Either Text Number), [Text])
\end{code} These functions lets new settings from scratch. text and number functions are wrapper to settings value. These last two functions are helpful at fromList uses, because hide Either datatype. \begin{code}
-- * Building Settings
-- | empty configurations
empty :: Settings
empty = Data.Map.empty
-- | fromList
fromList :: [(Text, (Bool, Either Text Number))] -> Settings
fromList = Data.Map.fromList
-- | wrapper to settings
text' :: Text -> (Bool, Either Text Number)
text' t = (True, Left t)
text :: Text -> Bool -> (Bool, Either Text Number)
text t = split id (const (Left t))
-- |wrapper to settings
number' :: Number -> (Bool, Either Text Number)
number' n = (True, Right n)
number :: Number -> Bool -> (Bool, Either Text Number)
number n = split id (const (Right n))
-- | 
priority :: Bool
priority = True
\end{code} We present raw access functions. These functions, such as, addSettings and getSettings are wrapper to function on mapping. These functions allow manipulation over Settings like add new setting or get value from previous added key. \begin{nocode} -- || Add new value to configuration --addSettings :: Text -> (Bool, Either Text Number) -> Settings -> Settings --addSettings k v = insert k v --addSettings1 :: Text -> (Bool -> (Bool, Either Text Number)) -> Settings -> Settings --addSettings1 k v = id -- || add new Text value --addText :: Text -> Text -> Settings -> Settings --addText k v = addSettings k (text v) -- || add new Number value --addNumber :: Text -> Number -> Settings -> Settings --addNumber k v = addSettings k (number v) \end{nocode} \begin{code}
-- * Directly access
-- | Get value from configuration
getSettings :: Text -> Settings -> Maybe (Either Text Number)
getSettings t = lookup t . Data.Map.map p2
--maybe Nothing (Just . p2) . lookup t 
-- | 
changeSettings' :: Text -> (Bool, Either Text Number) -> Settings -> Settings
changeSettings' k v = alter ((const . Just) v) k 
changeSettings :: Text -> (Bool -> (Bool, Either Text Number)) -> Settings -> Settings
changeSettings k v = alter (Just . maybe (v False) (v . p1)) k
\end{code} We recommend these functions instead raw access functions due to easy use. These functions explicit type of values and are designed to Point-Free approach. \begin{code}
-- * Easy access
-- | get Text value from Configurations
getText :: Text -> Settings -> Maybe Text
getText k = maybe Nothing (either Just (const Nothing)) . getSettings k
-- | get Number value from Configurations
getNumber :: Text -> Settings -> Maybe Number
getNumber k = maybe Nothing (either (const Nothing) Just) . getSettings k
-- | Change Text
changeText :: Text -> Text -> Settings -> Settings
changeText k v = changeSettings k (text v)
-- | Change Number
changeNumber :: Text -> Number -> Settings -> Settings
changeNumber k v = changeSettings k (number v)
\end{code} Joining and splitting settings are crucial operations at next modules to mix settings. This function doesn't work with keys that it have more priority than others. \begin{code}
-- * Merge and splitting
-- | Union 
union :: Settings -> Settings -> Settings
union a b = Data.Map.union a b
union1 :: Settings -> Settings -> Settings
union1 = Data.Map.unionWith (either (const) (flip const) . grd p1) 
--if p1 then const else const) a b
\end{code} \begin{nocode} -- || new union union2 :: Settings -> Settings -> Settings union2 a b = -- Data.Map.map (\(x,y) -> changeSettings x y) . ( Data.Map.union (p1 a) (p1 b), p2 a ++ p2 b) ch = --Data.List.foldr (\a b -> filterWithKey (p a) b) Data.Map.empty -- where p k = True Data.List.foldr (const id) Data.Map.empty -- where f = --Data.List.map -- (\k1 -> Data.Map.foldWithKey (const const) Data.Map.empty) -- [] -- where f k a = id \end{nocode}