module Azubi.Core.Syntax where
import Azubi.Core.Command
import Azubi.Core.Context
import Azubi.Core.Revertable
azubiConfig :: (Context a) => a -> [(a -> [Command])] -> [Command]
azubiConfig con commands =
concat $ map injectContext commands
where
injectContext f = f con
submodule :: (Context a) => [(a -> [Command])] -> a -> [Command]
submodule commands context =
concat $ map injectContext commands
where
injectContext f = f context
requires :: (Context a, Revertable a) => (a -> [Command]) -> (a -> [Command]) -> a -> [Command]
first `requires` sec = \context ->
if (isRevert context)
then
[ Dependency { body=(sec context)
, dependency=(first context)}]
else
[ Dependency { body=(first context)
, dependency=(sec context)}]
(&) :: (Context a) => [ (a -> [Command]) ] -> (a -> [Command] ) -> [ (a -> [Command])]
first & second = first ++ [ second ]
(!) :: (Revertable a) => [ (a -> [Command]) ] -> (a -> [Command] ) -> [ (a -> [Command])]
first ! second = first ++ [( second . toggleRevert ) ]
(&?&) :: (Revertable a) => [ (a -> [Command]) ] -> (a -> [Command] ) -> [ (a -> [Command])]
first &?& second = first ++ [ check ]
where check con =
if (isRevert con)
then []
else second con
(!?&) :: (Revertable a) => [ (a -> [Command]) ] -> (a -> [Command] ) -> [ (a -> [Command])]
first !?& second = first ++ [ check ]
where check con =
if (isRevert con)
then []
else second (setRevert con)
(&?!) :: (Revertable a) => [ (a -> [Command]) ] -> (a -> [Command] ) -> [ (a -> [Command])]
first &?! second = first ++ [ check ]
where check con =
if (isRevert con)
then second (setExectue con)
else []
(!?!) :: (Revertable a) => [ (a -> [Command]) ] -> (a -> [Command] ) -> [ (a -> [Command])]
first !?! second = first ++ [ check ]
where check con =
if (isRevert con)
then second con
else []