make Annex an opaque data type

Was a type alias; using newtype has the benefit that type errors will
show "Annex foo" rather than two lines of internal type nonsense. Yay!
There should be no other effects to size or runtime.

I've tried to do this at least twice before (each time I read RWH chapter 10);
finally understood how to this time.. sorta.
This commit is contained in:
Joey Hess 2011-08-19 14:28:07 -04:00
parent e97fede8cd
commit 021e8e1e0e

View file

@ -5,6 +5,8 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Annex ( module Annex (
Annex, Annex,
AnnexState(..), AnnexState(..),
@ -17,6 +19,7 @@ module Annex (
) where ) where
import Control.Monad.State import Control.Monad.State
import Control.Monad.IO.Control
import qualified Git import qualified Git
import Git.Queue import Git.Queue
@ -28,7 +31,14 @@ import Types.TrustLevel
import Types.UUID import Types.UUID
-- git-annex's monad -- git-annex's monad
type Annex = StateT AnnexState IO newtype Annex a = Annex { runAnnex :: StateT AnnexState IO a }
deriving (
Functor,
Monad,
MonadIO,
MonadControlIO,
MonadState AnnexState
)
-- internal state storage -- internal state storage
data AnnexState = AnnexState data AnnexState = AnnexState
@ -78,9 +88,9 @@ new gitrepo = newState `liftM` (liftIO . Git.configRead) gitrepo
{- performs an action in the Annex monad -} {- performs an action in the Annex monad -}
run :: AnnexState -> Annex a -> IO (a, AnnexState) run :: AnnexState -> Annex a -> IO (a, AnnexState)
run = flip runStateT run s a = runStateT (runAnnex a) s
eval :: AnnexState -> Annex a -> IO a eval :: AnnexState -> Annex a -> IO a
eval = flip evalStateT eval s a = evalStateT (runAnnex a) s
{- Gets a value from the internal state, selected by the passed value {- Gets a value from the internal state, selected by the passed value
- constructor. -} - constructor. -}