{-# LANGUAGE ExistentialQuantification, RankNTypes, FlexibleContexts, ScopedTypeVariables, ConstraintKinds #-} {- This module is part of Antisplice. Copyleft (c) 2014 Marvin Cohrs All wrongs reversed. Sharing is an act of love, not crime. Please share Antisplice with everyone you like. Antisplice is free software: you can redistribute it and/or modify it under the terms of the GNU Affero General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. Antisplice is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Affero General Public License for more details. You should have received a copy of the GNU Affero General Public License along with Antisplice. If not, see . -} -- | Provides operators for composing masked consumers module Game.Antisplice.MaskedSkills where import Data.Monoid import Game.Antisplice.Call import Game.Antisplice.Monad.Dungeon import Data.Chatty.None import Data.Chatty.Hetero -- | A special consumer whose conditions and actions rely on evaluation result masks data MaskedConsumer r = MasCon [PredMaskCond r] [PostMaskHandler r] -- | A special handler that relies on an evaluation result post-processing mask data PostMaskHandler r = forall po pr pt. (PostMask po r pr,Tuplify pr pt) => PMHandler po (pt -> Handler) -- | A special condition that relies on an evaluation result predicate mask data PredMaskCond r = forall p. PredMask p r => PMCond p instance Monoid (MaskedConsumer r) where mempty = MasCon [] [] (MasCon c1 h1) `mappend` (MasCon c2 h2) = MasCon (c1 ++ c2) (h1 ++ h2) instance None (MaskedConsumer r) where none = mempty infix 8 &-> -- | Composes a masked consumer from an evaluation result post-processing mask and a handler that relies on its result (&->) :: (PostMask po r pr, Tuplify pr pt) => po -> (pt -> Handler) -> MaskedConsumer r po &-> h = MasCon [] [PMHandler po h] infix 8 -&?-> -- | Composes a masked consumer from an evaluation result combi mask and a handler that relies on its possible result. Takes a third parameter for the correct type. In most cases you'll want '&?->' instead. (-&?->) :: (CombiMask cm r pm pom, PredMask pm r, PostMask pom r por, Tuplify por pot) => cm -> (pot -> Handler) -> r -> MaskedConsumer r c -&?-> h = \r -> MasCon [PMCond $ ctopred c r] [PMHandler (ctopost c r) h] infix 8 &?-> -- | Composes a masked consumer from an evaluation result combi mask and a handler that relies on its possible result. (&?->) :: (CombiMask cm r pm pom, PredMask pm r, PostMask pom r por, Tuplify por pot) => cm -> (pot -> Handler) -> MaskedConsumer r c &?-> h = (c -&?-> h) undefined {-handle :: (Tuplify pr pt, PostMask (a -> a) r pr) => (pt -> Handler) -> MaskedConsumer r handle h = id &-> h-} infixl 7 +? -- | Adds an evaluation result predicate mask to a masked consumer. (+?) :: PredMask p r => MaskedConsumer r -> p -> MaskedConsumer r mc +? p = mc <> MasCon [PMCond p] [] infixl 7 +& -- | Concatenates two masked consumers. (+&) :: MaskedConsumer r -> MaskedConsumer r -> MaskedConsumer r m1 +& m2 = m1 <> m2