Skip to content

Commit

Permalink
even more renaming
Browse files Browse the repository at this point in the history
  • Loading branch information
jamessanders committed Feb 19, 2011
1 parent b676e47 commit 9e100b4
Show file tree
Hide file tree
Showing 2 changed files with 17 additions and 17 deletions.
24 changes: 12 additions & 12 deletions src/Text/Twine/Eval/Context.hs
Expand Up @@ -9,7 +9,7 @@
, FunctionalDependencies
#-}

module Text.Twine.Eval.Context (emptyContext, ContextBinding (..)) where
module Text.Twine.Eval.Context (emptyContext, TemplateInterface (..)) where

import Data.ByteString.Char8 (ByteString)
import Data.Maybe
Expand All @@ -19,11 +19,11 @@ import qualified Data.ByteString.Char8 as C
import Control.Monad.Writer
import qualified Data.Map as M

class (Monad m) => ContextBinding m a | a -> m where
class (Monad m) => TemplateInterface m a | a -> m where
binding :: ByteString -> a -> m (TwineElement m)
makeIterable :: a -> m [TwineElement m]
makeString :: a -> m String
bind :: (ContextBinding m a) => a -> TwineElement m
bind :: (TemplateInterface m a) => a -> TwineElement m

binding _ _ = return TwineNull
makeIterable _ = return []
Expand All @@ -35,32 +35,32 @@ class (Monad m) => ContextBinding m a | a -> m where
}


instance (Monad m) => ContextBinding m (TwineElement m) where
instance (Monad m) => TemplateInterface m (TwineElement m) where
bind = id
makeString = return . show

instance (Monad m) => ContextBinding m ([TwineElement m] -> m (TwineElement m)) where
instance (Monad m) => TemplateInterface m ([TwineElement m] -> m (TwineElement m)) where
bind = TwineFunction

instance (Monad m) => ContextBinding m EmptyContext
instance (Monad m) => TemplateInterface m EmptyContext

instance (Monad m, ContextBinding m a) => ContextBinding m (Maybe a) where
instance (Monad m, TemplateInterface m a) => TemplateInterface m (Maybe a) where
bind (Just a) = bind a
bind Nothing = TwineNull

instance (Monad m) => ContextBinding m [(ByteString,TwineElement m)] where
instance (Monad m) => TemplateInterface m [(ByteString,TwineElement m)] where
binding k = return . fromMaybe TwineNull . lookup k

instance (Monad m) => ContextBinding m String where
instance (Monad m) => TemplateInterface m String where
bind = TwineString . C.pack

instance (Monad m) => ContextBinding m ByteString where
instance (Monad m) => TemplateInterface m ByteString where
bind a = TwineString a

instance (Monad m) => ContextBinding m Bool where
instance (Monad m) => TemplateInterface m Bool where
bind = TwineBool

instance (Monad m) => ContextBinding m (M.Map ByteString (TwineElement m)) where
instance (Monad m) => TemplateInterface m (M.Map ByteString (TwineElement m)) where
binding k = return . fromMaybe (TwineNull) . M.lookup k

emptyContext :: (Monad m) => TwineElement m
Expand Down
10 changes: 5 additions & 5 deletions src/Text/Twine/Eval/FancyContext.hs
Expand Up @@ -13,10 +13,10 @@ module Text.Twine.Eval.FancyContext where
import Text.Twine.Eval.Types
import Text.Twine.Eval.Context

instance (ContextBinding m a) => ContextBinding m [a] where
instance (TemplateInterface m a) => TemplateInterface m [a] where
bind = bind . CXListLike . map bind

instance (Monad m) => ContextBinding m (CXListLike m) where
instance (Monad m) => TemplateInterface m (CXListLike m) where
binding "length" = mbind . length . unCXListLike
binding "head" = mbind . head . unCXListLike
binding "tail" = mbind . tail . unCXListLike
Expand All @@ -39,13 +39,13 @@ instance (Monad m) => ContextBinding m (CXListLike m) where

------------------------------------------------------------------------

instance (Monad m) => ContextBinding m Int where
instance (Monad m) => TemplateInterface m Int where
bind = bind . CXInteger . fromIntegral

instance (Monad m) => ContextBinding m Integer where
instance (Monad m) => TemplateInterface m Integer where
bind = bind . CXInteger

instance (Monad m) => ContextBinding m CXInteger where
instance (Monad m) => TemplateInterface m CXInteger where
makeString = return . show . unCXInteger
binding "toInteger" = return . TwineInteger . unCXInteger
binding "even?" = mbind . even . unCXInteger
Expand Down

0 comments on commit 9e100b4

Please sign in to comment.