{-#LANGUAGE FlexibleContexts,FlexibleInstances,UndecidableInstances #-} -- MultiParamTypeClasses, {- Module : examples/PrivLib Copyright : (c) Mark Snyder 2012. License : BSD-style Maintainer : Mark Snyder, msnyde14@gmu.edu Stability : experimental Portability : non-portable (multi-param classes, functional dependencies) -} module PrivLib( getV, putV, TyPos, TyPosT, runPos, runPosT, MonadPos(..) ) where import Control.Monad.StateX data PRIV = PRIV deriving (Show, Eq) instance Index PRIV where getVal = PRIV getV :: (MonadStateX PRIV Int m) => m Int getV = getx PRIV putV :: (MonadStateX PRIV Int m) => Int -> m () putV v = putx PRIV (if v<=0 then abs v else v) -- 'unprivileged' types for the regular and transformer versions. type TyPos a = StateX PRIV Int a type TyPosT m a = StateTX PRIV Int m a -- 'unprivileged' run functions for the regular and transformer versions. runPos start = flip (runStateX PRIV) (abs start) runPosT start = flip (runStateTX PRIV) (abs start) -- 'unprivileged' class that hides our use of the StateX monad. class (MonadStateX PRIV Int m) => MonadPos m where instance (MonadStateX PRIV Int m) => MonadPos m where