{- This file is part of settings. - - Written in 2015 by fr33domlover . - - ♡ Copying is an act of love. Please copy, reuse and share. - - The author(s) have dedicated all copyright and related and neighboring - rights to this software to the public domain worldwide. This software is - distributed without any warranty. - - You should have received a copy of the CC0 Public Domain Dedication along - with this software. If not, see - . -} module Data.Settings.Option ( mkOptionV , mkOptionS ) where import Control.Monad (liftM) import Data.Bool (bool) import Data.Settings.Types mkOptionV :: (Monad m, OptionValue v) => m v -> (v -> m Bool) -> m () -> Option m mkOptionV get set reset = Option { optGet = liftM (showOption) get , optSet = \ s -> case readOption s of Nothing -> return $ Just $ InvalidValueForType s Just v -> liftM (bool (Just $ InvalidValue s) Nothing) $ set v , optReset = reset } mkOptionS :: (MonadSettings m s, OptionValue v) => (s -> v) -> (v -> s -> Maybe s) -> (s -> (Maybe v, s)) -> (v -> m ()) -- callback -> Option m mkOptionS get set reset cb = mkOptionV (liftM get getSettings) (\ v -> do s <- getSettings case set v s of Just s' -> putSettings s' >> cb v >> return True Nothing -> return False ) ( do s <- getSettings let (mv, s') = reset s putSettings s' case mv of Just v -> cb v Nothing -> return () )