Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Examples.Ltl.HigherOrder
Description
A tutorial for how to use Logic.Ltl with higher-order effects. The explanations here assume you've understood the simple tutorial in Examples.Ltl.Simple.
Synopsis
- data MiniLangValue
- data MiniLangError
- class Monad m => MonadMiniLang m where
- push :: MiniLangValue -> m ()
- pop :: m MiniLangValue
- echo :: String -> m ()
- if_ :: m a -> m a -> m a
- while_ :: m () -> m ()
- type MiniLangT m = ExceptT MiniLangError (WriterT String (StateT [MiniLangValue] m))
- runMiniLangT :: Functor m => MiniLangT m a -> m ((Either MiniLangError a, String), [MiniLangValue])
- data MonadMiniLangEffect :: Effect where
- Push :: forall (m :: Type -> Type). MiniLangValue -> MonadMiniLangEffect m ()
- Pop :: forall (m :: Type -> Type). MonadMiniLangEffect m MiniLangValue
- Echo :: forall (m :: Type -> Type). String -> MonadMiniLangEffect m ()
- If_ :: forall (m :: Type -> Type) (a :: Type). (m a) -> (m a) -> MonadMiniLangEffect m a
- While_ :: forall (m :: Type -> Type). (m ()) -> MonadMiniLangEffect m ()
- fibonacciExample :: (MonadError MiniLangError m, MonadMiniLang m) => Integer -> m Integer
- gcdExample :: (MonadError MiniLangError m, MonadMiniLang m) => Integer -> Integer -> m Integer
- popInteger :: (MonadError MiniLangError m, MonadMiniLang m) => m Integer
- pushInteger :: MonadMiniLang m => Integer -> m ()
- popBoolean :: (MonadError MiniLangError m, MonadMiniLang m) => m Bool
- pushBoolean :: MonadMiniLang m => Bool -> m ()
- data MiniLangMod = MiniLangMod {}
- popBoolMiniLangMod :: (Bool -> Maybe Bool) -> MiniLangMod
- popIntegerMiniLangMod :: (Integer -> Maybe Integer) -> MiniLangMod
- popMiniLangMod :: (Bool -> Maybe Bool) -> (Integer -> Maybe Integer) -> MiniLangMod
- pushBoolMiniLangMod :: (Bool -> Maybe Bool) -> MiniLangMod
- pushIntegerMiniLangMod :: (Integer -> Maybe Integer) -> MiniLangMod
- pushMiniLangMod :: (Bool -> Maybe Bool) -> (Integer -> Maybe Integer) -> MiniLangMod
- flipBools :: MiniLangMod
- flipIntegers :: MiniLangMod
- flipBoth :: MiniLangMod
- moduloMiniLangMod :: Integer -> MiniLangMod
- interpretAndRunMiniLang :: LtlAST MiniLangMod '[MonadMiniLangEffect, MonadErrorEffect MiniLangError] a -> [((Either MiniLangError a, String), [MiniLangValue])]
- exampleSomewhere :: [((Either MiniLangError Integer, String), [MiniLangValue])]
- exampleIf :: MiniLangMod -> Bool -> [((Either MiniLangError (), String), [MiniLangValue])]
- exampleFlipFibonacci :: Bool
Example domain specification
Our domain will be a low level, Turing-complete, abstract machine
called MonadMiniLang
which is based on a stack of integers and
booleans and can raise three different errors. Values can be popped
and pushed, arbitrary text can be printed, and two control
structures are present: if_
and while_
.
These two latter operations are what makes MonadMiniLang
a
higher order domain: There are nesting operations, that is,
operations that have sequences of operations in the same monad as
parameters.
In Graft, nested operations must occur in positive position for
conceptual and technical reasons. As a reminder, x
is in
positive position in t
if it stands before an even number of
->
s, otherwise it is in negative position. A few examples:
- In
a -> b
,a
is in negative position,b
in positive - position.
- In
(a -> b) -> c
,a
andc
are in positive position, andb
is in negative position. - In
Maybe ((a -> [b]) -> c) -> d
,d
andb
are in positive position, anda
andc
are in negative position.
data MiniLangValue Source #
Constructors
MiniLangInteger Integer | |
MiniLangBoolean Bool |
Instances
Show MiniLangValue Source # | |
Defined in Examples.Ltl.HigherOrder Methods showsPrec :: Int -> MiniLangValue -> ShowS # show :: MiniLangValue -> String # showList :: [MiniLangValue] -> ShowS # | |
Eq MiniLangValue Source # | |
Defined in Examples.Ltl.HigherOrder Methods (==) :: MiniLangValue -> MiniLangValue -> Bool # (/=) :: MiniLangValue -> MiniLangValue -> Bool # | |
MonadPlus m => Alternative (MiniLangT m) Source # | |
MonadPlus m => MonadPlus (MiniLangT m) Source # | |
Monad m => MonadMiniLang (MiniLangT m) Source # | |
data MiniLangError Source #
Constructors
StackUnderflow | |
ExpectedBoolean | |
ExpectedInteger |
Instances
Show MiniLangError Source # | |
Defined in Examples.Ltl.HigherOrder Methods showsPrec :: Int -> MiniLangError -> ShowS # show :: MiniLangError -> String # showList :: [MiniLangError] -> ShowS # | |
Eq MiniLangError Source # | |
Defined in Examples.Ltl.HigherOrder Methods (==) :: MiniLangError -> MiniLangError -> Bool # (/=) :: MiniLangError -> MiniLangError -> Bool # | |
MonadPlus m => Alternative (MiniLangT m) Source # | |
MonadPlus m => MonadPlus (MiniLangT m) Source # | |
Monad m => MonadMiniLang (MiniLangT m) Source # | |
class Monad m => MonadMiniLang m where Source #
Methods
push :: MiniLangValue -> m () Source #
pop :: m MiniLangValue Source #
echo :: String -> m () Source #
Instances
((), EffectInject MonadMiniLangEffect ops) => MonadMiniLang (AST ops) Source # | |
Monad m => MonadMiniLang (MiniLangT m) Source # | |
A concrete implementation for our domain: we use
- a list of values as inner state to account for the stack
- a writer to allow printing strings using
echo
- an exception to cover possible errors
type MiniLangT m = ExceptT MiniLangError (WriterT String (StateT [MiniLangValue] m)) Source #
runMiniLangT :: Functor m => MiniLangT m a -> m ((Either MiniLangError a, String), [MiniLangValue]) Source #
As in the simple tutorial, the MonadPlus
instance is necessary
boilerplate for the interpretation of Ltl
formulas, since there
might be several ways to satisfy one formula, and we want to try
them all.
Using the effect system
To obtain the effects associated with MiniLang for free, we call the same macros as in Examples.Ltl.Simple which also work in higher order settings.
data MonadMiniLangEffect :: Effect where Source #
Constructors
Push :: forall (m :: Type -> Type). MiniLangValue -> MonadMiniLangEffect m () | |
Pop :: forall (m :: Type -> Type). MonadMiniLangEffect m MiniLangValue | |
Echo :: forall (m :: Type -> Type). String -> MonadMiniLangEffect m () | |
If_ :: forall (m :: Type -> Type) (a :: Type). (m a) -> (m a) -> MonadMiniLangEffect m a | |
While_ :: forall (m :: Type -> Type). (m ()) -> MonadMiniLangEffect m () |
Instances
((), MonadMiniLang m) => InterpretEffect m MonadMiniLangEffect Source # | |
Defined in Examples.Ltl.HigherOrder Methods interpretEffect :: forall (ops :: [Effect]) a. (forall b. AST ops b -> m b) -> MonadMiniLangEffect (AST ops) a -> m a Source # | |
(MonadPlus m, MonadError MiniLangError m, MonadMiniLang m) => InterpretLtlHigherOrder MiniLangMod m MonadMiniLangEffect Source # | |
Defined in Examples.Ltl.HigherOrder Methods interpretLtlHigherOrder :: forall (ops :: [Effect]) a. MonadMiniLangEffect (AST ops) a -> LtlInterpHigherOrder MiniLangMod m ops a Source # |
Example programs in MonadMiniLang
fibonacciExample :: (MonadError MiniLangError m, MonadMiniLang m) => Integer -> m Integer Source #
A program that computes the nth Fibonacci number.
gcdExample :: (MonadError MiniLangError m, MonadMiniLang m) => Integer -> Integer -> m Integer Source #
A program that computes the greatest common divisor of two numbers.
Helper functions used in the example programs
popInteger :: (MonadError MiniLangError m, MonadMiniLang m) => m Integer Source #
pushInteger :: MonadMiniLang m => Integer -> m () Source #
popBoolean :: (MonadError MiniLangError m, MonadMiniLang m) => m Bool Source #
pushBoolean :: MonadMiniLang m => Bool -> m () Source #
Defining single step modifications
Our type of modifications is a conjunction of a function to be
applied before pushing a value, and a function to be applied after
poping a value. To combine those within a Semigroup instance, we
compose them while accounting for the fact that they can return
Nothing
.
Again, as explained in the simple tutorial, the
Semigroup
instance is necessary because evaluation of Ltl
formulas might sometimes make it necessary to apply more than one
modification on the same operation.
data MiniLangMod Source #
Constructors
MiniLangMod | |
Fields
|
Instances
Semigroup MiniLangMod Source # | |
Defined in Examples.Ltl.HigherOrder Methods (<>) :: MiniLangMod -> MiniLangMod -> MiniLangMod # sconcat :: NonEmpty MiniLangMod -> MiniLangMod # stimes :: Integral b => b -> MiniLangMod -> MiniLangMod # | |
(MonadPlus m, MonadError MiniLangError m, MonadMiniLang m) => InterpretLtlHigherOrder MiniLangMod m MonadMiniLangEffect Source # | |
Defined in Examples.Ltl.HigherOrder Methods interpretLtlHigherOrder :: forall (ops :: [Effect]) a. MonadMiniLangEffect (AST ops) a -> LtlInterpHigherOrder MiniLangMod m ops a Source # |
Meaning is given to the single step modifications through their
interpretation over our domain. This is what the class
InterpretLtlHigherOrder
is for. There are two main differences
with the first order case:
- The interpretation function directly handles
Ltl
formulas. (Remember that theInterpretMod
instance in the simple tutorial only has to handle single-step modifications.) This is because the approach based on applying atomic modifications to single operations breaks down for higher-order operations: a single higher-order operation may contain sequences (AST
s) of operations. - An explicit distinction needs to be made between first-order and
higher-order effect constructors, by using
Direct
andNested
respectively.
Considering the second difference:
- Using
Direct
signals that the operation at hand is first order, and you can proceed as if writing anInterpretMod
instance, as explained in the simple tutorial. - Using
Nested
means the operation is of higher order. This case is detailed below.
Handling higher order operations:
In the first order setting, we have the convenient class
InterpretMod
which allows us to specify how single-step
modifications should be applied on operations. In the higher order
setting the question is different: applying a single step
modification on a nested operation makes no sense because it will
likely contain several such operations, thus we provide the whole
set of formulas to be applied currently and leave it to the user as
to how they should be handling those. While it seems complicated,
it is actually pretty straighforward in most cases as the user has
sufficient domain knowledge to know how and when the nested blocks
will be executed.
In the example:
Let's explain if_
here. The typical behaviour of if_
will be to
evaluate the condition and pass the formula that modifies the
remainder of the computation to either of the two branches,
depending on whether the condition was true or false. In the case
of our example, evaluation the condition is itself an operation,
namely a pop
. So, we will first consume the next single step
modification and apply it to that pop
. If that was successful,
we'll pass on the remaining formulas to the correct block depending
on the result of the (possibly modified) result of evaluating the
condition.
Note how we use the function nowLaterList
which, from a list of
Ltl formulas, creates a list of pairs of a modification to be
applied now and the remaining formulas. This function will likely
often be called in higher order operations.
Smart constructors of modifications
popBoolMiniLangMod :: (Bool -> Maybe Bool) -> MiniLangMod Source #
Modify boolean values on pop
popIntegerMiniLangMod :: (Integer -> Maybe Integer) -> MiniLangMod Source #
Modify integer values on pop
popMiniLangMod :: (Bool -> Maybe Bool) -> (Integer -> Maybe Integer) -> MiniLangMod Source #
Modify all values on pop
pushBoolMiniLangMod :: (Bool -> Maybe Bool) -> MiniLangMod Source #
Modify booleans on push
pushIntegerMiniLangMod :: (Integer -> Maybe Integer) -> MiniLangMod Source #
Modify integers on push
pushMiniLangMod :: (Bool -> Maybe Bool) -> (Integer -> Maybe Integer) -> MiniLangMod Source #
Modify all values on push
flipBools :: MiniLangMod Source #
Negate booleans on pop and push
flipIntegers :: MiniLangMod Source #
Negate integers on pop and push
flipBoth :: MiniLangMod Source #
Negate all values on pop and push
moduloMiniLangMod :: Integer -> MiniLangMod Source #
Apply the modulo operation on pop and push for integers
Running modified MiniLang programs
As in the simple tutorial, we can use the function
interpretLtlAST
to obtain a function that will interpret an
LtlAST
of MonadMiniLangEffect
and MonadErrorEffect
.
Note that the LtlInstanceKind
for the MonadMiniLangEffect
is
InterpretLtlHigherOrderTag
, since that's the instance that we
implemented above: InterpretLtlHigherOrder MiniLangMod m
MonadMiniLangEffect
.
Again, the InterpretEffectStateful
instance for MonadErrorEffect
MiniLangError
is the "passthrough" instance imported from
Effect.Error.Passthtrough, which ignores all modifications: We're
only interested in modifying MonadMiniLang
operations in the
program, not its generic error handling.
interpretAndRunMiniLang :: LtlAST MiniLangMod '[MonadMiniLangEffect, MonadErrorEffect MiniLangError] a -> [((Either MiniLangError a, String), [MiniLangValue])] Source #
As in the simple simple tutorial, we can apply the modifyLtl
function to modify the MonadMiniLang
operations in the program.
exampleSomewhere :: [((Either MiniLangError Integer, String), [MiniLangValue])] Source #
>>>
exampleSomewhere
[((Right -42,"Pushing 42"),[]), ((Right -42,"Pushing 42"),[])]
Let's look at a more interesting example with a higher-order
operation, if_
.
exampleIf :: MiniLangMod -> Bool -> [((Either MiniLangError (), String), [MiniLangValue])] Source #
>>>
exampleIf flipIntegers True
[((Right (),""),[MiniLangInteger (-42)]]
>>>
exampleIf flipIntegers False
[]
The two runs above show that we only modify the "else" branch of
the if_
when it is executed: in the second run, no modification
is applied, because no push or pop involving an integer happens.
The next two runs are more involved, because we modify booleans,
which are intrinsically very relevant for if_
s. Let's mark the
places that are potentially modified:
do pushBoolean intOrBool -- (1) because we push a boolean if_ -- (2) because 'if_' pushes a boolean (pushInteger 42) (pushBoolean True) -- (3) because we push a boolean
The modality somewhere
requires that we either modify the
pushBoolean
at (1), or modify some later push
or pop
of a
boolean. If intOrBool
is initially True
, that means we have two
options:
- modify at (1), which means that the we'll
pop
aFalse
at (2). In this scenario, we'll execute the 'else' branch, which willpush
aTrue
at (3). - modify at (2), which also means that we'll
pop
aFalse
at (2). We'll consequently also execute the execute the 'else' branch, which willpush
aTrue
at (3).
Note that we'll never apply a modification at (3), because in both
cases, the requirements of somewhere
are already satisfied.
>>>
exampleIf flipBools True
[((Right (), ""), [MiniLangBoolean True]), ((Right (), ""), [MiniLangBoolean True])]
For our last run, let's look at the case where intOrBool
is
False
. In that case, the following three scenarios are possible:
- modify at (1), which means that we'll
pop
aTrue
at (2). So, we'll execute the 'then' branch, which willpush
a '42'. - modify at (2), which means that we'll
pop
aTrue
at (2). So, we'll execute the 'then' branch, which willpush
a '42'. - If we don't modify at (1) or (2), we'll execute the 'else'
branch, which will
push
aFalse
(modified fromTrue
) at (3).
>>>
exampleIf flipBools False
[((Right (),""),[MiniLangInteger 42]), ((Right (),""),[MiniLangInteger 42]), ((Right (),""),[MiniLangBoolean False])]
Finally, for a more testing-flavoured example, we can check the
property that the programs only interact with the stack through the
push
and pop
operations, by applying everywhere
flipBoth
. Effectively, this modification means that the entries on
the stack will always be the inverse of their "actual" values, and
that the meaning of push
and pop
also contains reversing this
polarity.
>>>
exampleFlipFibonacci
True