-----------------------------------------------------------------------------
-- Copyright 2019, Advise-Me project team. This file is distributed under 
-- the terms of the Apache License 2.0. For more information, see the files
-- "LICENSE.txt" and "NOTICE.txt", which are included in the distribution.
-----------------------------------------------------------------------------
-- |
-- Maintainer  :  bastiaan.heeren@ou.nl
-- Stability   :  provisional
-- Portability :  portable (depends on ghc)
--
-- This module defines the language of the subexpression recognizer.
-- 
-- We make use of the open data-type `Expr` to combine both already existing constructors and new constructors defined here.
-- 
-- If you want to add a new symbol to the language, you must do the following:
-- 
-- * Create the symbol and corresponding `Expr` constructor in this module
-- * Add a function named 'pFindSubXXX', in "Recognize.SubExpr.Recognizer". Add a call to that function in `pFindSubExpr`.
-- * Add existence functions in "Recognize.SubExpr.Functions".
-- * Some functions in "Recognize.SubExpr.Functions" may require modification, such as `cleanExpr`. Make sure you thoroughly go over the functions in that file and modify where necessary.
--
-----------------------------------------------------------------------------

module Recognize.SubExpr.Symbols where

import Ideas.Common.Rewriting
import Domain.Math.Expr.Data

-------------------------------------------------------------
-- Symbols
-------------------------------------------------------------

buggySymbol :: Symbol
buggySymbol = newSymbol "buggySymbol"

orSymbol :: Symbol
orSymbol = newSymbol "or"

andSymbol :: Symbol
andSymbol = newSymbol "and"

varSymbol :: Symbol
varSymbol = newSymbol "var"

ltSymbol :: Symbol
ltSymbol = newSymbol "lt"

matchSymbol :: Symbol
matchSymbol = newSymbol "match"

magicVarSymbol :: Symbol
magicVarSymbol = newSymbol "magicVar"

magicNatSymbol :: Symbol
magicNatSymbol = newSymbol "magicNat"

magicNumberSymbol :: Symbol
magicNumberSymbol = newSymbol "magicNumber"

labelSymbol :: Symbol
labelSymbol = newSymbol "label"

stopSymbol :: Symbol
stopSymbol = newSymbol "stop"

simSymbol :: Symbol
simSymbol = newSymbol "simpl"

noSimSymbol :: Symbol
noSimSymbol = newSymbol "noSimpl"

subSymbol :: Symbol
subSymbol = newSymbol "sub"

--------------------------------------------------------------
-- Expression defined using the above symbols
--------------------------------------------------------------

-- | Gives us a way to say that matching to an expression is deemed incorrect.
--
-- It takes two expressions. Matching the first is 'correct' and matching the second is 'incorrect.
--
-- Other than that, it behaves similarly to 'or'.
infixl 3 <!>
(<!>) :: Expr -> Expr -> Expr
a <!> b = Sym buggySymbol [a, b]

-- | 'or' between expressions
--
-- Match the first or the second. It is possible for both to be matched.
infixl 3 <?>
(<?>) :: Expr -> Expr -> Expr
a <?> b = Sym orSymbol [a,b]

-- | 'and' between expressions
--
-- Both expressions must be matched
infixl 0 <&>
(<&>) :: Expr -> Expr -> Expr
x <&> y = Sym andSymbol [x,y]

-- | Mutable variable.
--
-- This is different from the `Expr` Var constructor in that this var acts as a reference to some expression.
--
-- It is also possible for this expression to change, but only from some magic expression type to some more concrete expression type.
var :: String -> Expr
var s = Sym varSymbol [Var s]

-- | Let expression
--
-- Introduces mutable variables by assigning it some default value.
--
-- It takes a string to be used as an identifier (make sure it is unique). The default value and
--
-- a function whose argument is the introduced mutable variable.
lt :: String -> Expr -> (Expr -> Expr) -> Expr
lt s e f = Sym ltSymbol [Var s, e, f $ var s]

-- | Tells us that an expression has been matched by the recognizer
matchExpr :: Expr -> Expr
matchExpr e = Sym matchSymbol [e] -- clean?

-- | Matches any variable
newMagicVar :: Expr
newMagicVar = Sym magicVarSymbol []

-- | Matches any natural number
newMagicNat :: Expr
newMagicNat = Sym magicNatSymbol []

-- | Matches any number
newMagicNumber :: Expr
newMagicNumber = Sym magicNumberSymbol []

-- | Label an expression (generates an `Attribute`)
lbl :: String -> Expr -> Expr
lbl x e = Sym labelSymbol [Var x, e]

-- | Same as `lbl`, but also includes an expression in the label.
lblE :: String -> Expr -> Expr -> Expr
lblE l x e = Sym labelSymbol [Var l, x, e]

-- | Stops further traversing into the expression
stop :: Expr -> Expr
stop x = Sym stopSymbol [x]

-- | An expression must be completely simplified before we consider it to be matched.
sim :: Expr -> Expr
sim x = Sym simSymbol [x]

-- | No simplification allowed
--
-- Turns of simplification in the recognizer
noSim :: Expr -> Expr
noSim x = Sym noSimSymbol [x]

-- | First requires a normalized matching before a simplified form can match
sub :: Expr -> Expr
sub x = Sym subSymbol [x]