Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
This top-level module contains just a tutorial, which you can read below. It will help you figure out which of the sub-modules you need, and how to use them.
Tutorial
Concepts
For a real usage example, see the funbot package.
This library works with 2 components of your application state:
- Application settings value, of any type you like. Usually this is a record of a type you define specifically for your application. It can be a value just for settings, or, if modifiable settings are stored in various parts of your state, it can be the state value itself.
- A settings tree, of type
Section
(defined in Data.Settings.Types). This is a user interface component for accessing the settings values as a tree with labeled nodes. If your settings tree never changes, you can use a Haskell value directly for it. It if changes, add it to your application state so that it can be modified as needed during run time.
The idea is that you freely use whatever you like for the settings values,
and the settings tree is a UI component added on top without interfering
with your program logic code. Persistence using simple periodic exports to
JSON is available in the json-state
package, but you can use any other
solution as needed, e.g. the acid-state package.
Settings Tree Basics
In order to understand the layers of the API, we'll examine it bottom-up. We'll start with the generic flexible parts and move towards the more specific but simpler and more convenient ones. You'll likely need a bit of both sides, so it's probably best to taste both.
Suppose we're writing a terminal based text editor, like nano or vim.
The UI allows the user to enter commands like get x.y.z
or set x.y.z val
which manipulate the settings.
Let's define a type for settings. It may look like this:
data Settings = Settings { setsTabWidth :: Int , setsFont :: T.Text , setsTextSize :: Int , setsColorScheme :: T.Text }
For simplicity, suppose the settings tree won't be changing, so all we need in our application state is the settings. Let's use this:
data AppState = AppState { appOpenFiles :: [FilePath] , appUI :: Widget , appSettings :: Settings }
If we wanted to allow the settings tree structure to change, we'd have a field for it too in the app state record.
This will be our monad:
type App = StateT AppState IO
Now let's define a settings tree. A settings tree is the top-level section of it. Each such section consists of two things: A set of settings options, and a set of subsections. An empty tree looks like this:
import Data.Settings.Section (empty) stree :: Section App stree = empty
Which is equivalent to:
import qualified Data.HashMap.Lazy as M stree :: Section App stree = Section { secOpts = M.empty , secSubs = M.empty }
The secOpts
field is a map between option names and Option
values. The
secSubs
field is a map between subsection names and Section
values. We
can then refer to a specific tree node using period-separated syntax. For
example, if we have a tree with a single top-level option "a"
, we can
refer to it in the UI simply a "a"
. If we have a tree with a subsection
"s"
and under it an option "a"
, we refer to that section as "a"
and to the option under it as "s.a"
. And so on, we can have arbitrarily
deep nesting of sections and options, e.g. "s.t.u.v.w.x.a"
.
It is possible for a section or option name to contain a period. In that case, the period must be escaped using a backslash before it. To specify a literal backslash, escape it too, i.e. use two backslashes. It is also possible different separator characters instead of a period.
The low-level flexible way to define a settings tree is by using Option
value contructors directly. Let's define a simple flat tree with 4 options
and no subsections.
The Option
fields are monadic actions in our application monad, App
.
{-# LANGUAGE OverloadedStrings #-} import Control.Monad.Trans.State import Data.Settings.Types import Text.Read (readMaybe) import qualified Data.HashMap.Lazy as M import qualified Data.Text as T -- Convenience wrappers to make the code shorter -- Perhaps a good chance to use lens? getS = gets appSettings putS sets = modify $ \ app -> app { appSettings = sets } modifyS f = modify $ \ app -> app { appSettings = f $ appSettings app } stree :: Section App stree = Section { secOpts = M.fromList [ ( "tab-width" , Option { optGet = liftM (T.pack . show . setsTabWidth) getS , optSet = \ val -> case readMaybe $ T.unpack val of Just n -> do modifyS $ \ s -> s { setsTabWidth = n } return Nothing Nothing -> return $ Just $ InvalidValueForType val , optReset = modifyS $ \ s -> s { setsTabWidth = 4 } } ) , ( "font" , Option {- ... similar fashion ... -} ) , ( "text-size" , Option {- ... similar fashion ... -} ) , ( "color-scheme" , Option {- ... similar fashion ... -} ) ] , secSubs = M.empty }
Building a Settings UI
We'll see higher level alternatives later. Let's see how to contruct the settings UI now. The Data.Settings.Iterface provides a set of high-level functions you can use on your UI code. You just need to wrap them with UI actions like error message (e.g. invalid value) and feedback for successful operations.
Before we can use those functions, we need to make our application monad an
instance of the MonadSettings
(multi-parameter) typeclass:
instance MonadSettings App Settings where getSettings = getS putSettings = putS modifySettings = modifyS getSTree = return stree
Now, suppose the user enters the command get x.y.z
in our text editor's
command input line. This should return a friendly result. If x.y.z
is a
valid path in our settings tree leading to an option value, display that
value. If it's a section, display a list of the options and subsections it
contains. If it's neither, i.e. the path is invalid, report the error.
Such a UI can easily be constructed using functions in
Data.Settings.Interface, e.g. see the query
function. Using the values it returns, you can construct UI strings to
display on the screen.
For example, in our case we'd want get
to display the top-level tree
contents, get tab-width
to display a number (4 by default) and get foo
to display an error no such option or section.
Settings Tree Definition Tools
Let's go back to defining the settings tree. Some things we could improve:
- We defined
getS
and related small functions, and used them when we defined theMonadSettings
instance. Instead, we can first define the instance and then just use its methods in our settings free definition if needed. - The usage of
readMaybe
andshow
allowed us to easily and quickly wrap the tab width, anInt
value, by the string-based interface. But with larger settings records and more value types, we'd want something more robust and appropriate for UI. For example, if we did this for aBool
field, the user would have to type inset x.y.z True
whileset x.y.z yes
wouldn't work. Why tie the UI to the way booleans are written in Haskell? We can have true, TRUE, True, yes, Yes, 1 etc. all meanTrue
. Be flexible and user friendly. - Once we write the
MonadSettings
instance, instead of using its methods directly (like we usedgetS
etc.) we can have wrappers do it for us, so that we only need to write functions operating over theSettings
type directly, making our code simple and readable and easy to tweak.
Let's start with the second point, wrapping typed settings values with UI,
e.g. like the example given for booleans above. The Data.Settings.Option
module provides the mkOptionV
function. This function wraps the type
details for us, if we supply instances of the OptionValue
class. Let's
define an instance for Int
, which is the type of 2 out of the 4 fields in
our Settings
type. Generally, you'd want to define instances for all the
relevant field types in your settings type, e.g. perhaps also Bool
and
Float
and custom enum tyes and so on, depending on your requirements and
UI designs.
instace OptionValue Int where readOption = readMaybe . T.unpack showOption = T.pack . show typeName = const "Integer"
And here's an instance for Bool
:
instace OptionValue Bool where readOption s | sl `elem` ["true, "yes", "on", "1"] = Just True | sl `elem` ["false", "no", "off", "0"] = Just False | otherwise = Nothing where sl = T.toLower s showOption = bool "False" "True" typeName = const "Boolean"
Now, using mkOptionV
, and this time also using the MonadSettings
functions, we can redefine the tab width option like this:
mkOptionV (liftM setsTabWidth getSettings) (\ n -> do modifySettings $ \ s -> s { setsTabWidth = n } return True ) (modifySettings $ \ s -> s { setsTabWidth = 4 })
Now let's improve further. This will be the highest level of the API. Given
a MonadSettings
instance, the repetitive parts of the code can be cleaned
further, by using the mkOptionS
function.
mkOptionS setsTabWidth (\ n s -> Just s { setsTabWidth = n }) (\ s -> (Just 4, s { setsTabWidth = 4 })) (const $ return ())
Perhaps a bit cleaner form removing duplication is this:
mkOptionS setsTabWidth (\ n s -> Just $ set n s) (\ s -> (Just defval, set defval s)) (const $ return ()) where set n s = s { setsTabWidth = n } defval = 4
The last argument is a callback action to be run when a successful set or reset of the value occurs.
Settings Tree Dynamic Modification
Modification simply requires holding the tree as application state, and
changing as needed. Removing sections, adding options and so on. There is an
API in Data.Settings.Section for working with the settings tree, and since
unordered maps are being used, you may also find Data.HashMap.Lazy useful
(from unordered-containers
package).