-----------------------------------------------------------------------------
-- 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)
--
-----------------------------------------------------------------------------

module Recognize.Data.Definition where

import Domain.Math.Data.Relation
import Ideas.Common.Rewriting
import Ideas.Common.View

type Definition a = (String, a)

definitionView :: WithVars a => View (Relation a) (Definition a)
definitionView = makeView toDefinition fromDefinition

toDefinition :: WithVars a => Relation a -> Maybe (Definition a)
toDefinition r | relationType r == EqualTo
               , Just v <- getVariable (leftHandSide r) = Just (v, rightHandSide r)
               | relationType r == EqualTo
               , Just v <- getVariable (rightHandSide r) = Just (v, leftHandSide r)
              | otherwise = Nothing

fromDefinition :: WithVars a => Definition a -> Relation a
fromDefinition (s,e) = variable s .==. e