-- Copyright 2024 United States Government as represented by the Administrator
-- of the National Aeronautics and Space Administration. All Rights Reserved.
--
-- Disclaimers
--
-- No Warranty: THE SUBJECT SOFTWARE IS PROVIDED "AS IS" WITHOUT ANY WARRANTY
-- OF ANY KIND, EITHER EXPRESSED, IMPLIED, OR STATUTORY, INCLUDING, BUT NOT
-- LIMITED TO, ANY WARRANTY THAT THE SUBJECT SOFTWARE WILL CONFORM TO
-- SPECIFICATIONS, ANY IMPLIED WARRANTIES OF MERCHANTABILITY, FITNESS FOR A
-- PARTICULAR PURPOSE, OR FREEDOM FROM INFRINGEMENT, ANY WARRANTY THAT THE
-- SUBJECT SOFTWARE WILL BE ERROR FREE, OR ANY WARRANTY THAT DOCUMENTATION, IF
-- PROVIDED, WILL CONFORM TO THE SUBJECT SOFTWARE. THIS AGREEMENT DOES NOT, IN
-- ANY MANNER, CONSTITUTE AN ENDORSEMENT BY GOVERNMENT AGENCY OR ANY PRIOR
-- RECIPIENT OF ANY RESULTS, RESULTING DESIGNS, HARDWARE, SOFTWARE PRODUCTS OR
-- ANY OTHER APPLICATIONS RESULTING FROM USE OF THE SUBJECT SOFTWARE. FURTHER,
-- GOVERNMENT AGENCY DISCLAIMS ALL WARRANTIES AND LIABILITIES REGARDING
-- THIRD-PARTY SOFTWARE, IF PRESENT IN THE ORIGINAL SOFTWARE, AND DISTRIBUTES
-- IT "AS IS."
--
-- Waiver and Indemnity: RECIPIENT AGREES TO WAIVE ANY AND ALL CLAIMS AGAINST
-- THE UNITED STATES GOVERNMENT, ITS CONTRACTORS AND SUBCONTRACTORS, AS WELL AS
-- ANY PRIOR RECIPIENT. IF RECIPIENT'S USE OF THE SUBJECT SOFTWARE RESULTS IN
-- ANY LIABILITIES, DEMANDS, DAMAGES, EXPENSES OR LOSSES ARISING FROM SUCH USE,
-- INCLUDING ANY DAMAGES FROM PRODUCTS BASED ON, OR RESULTING FROM, RECIPIENT'S
-- USE OF THE SUBJECT SOFTWARE, RECIPIENT SHALL INDEMNIFY AND HOLD HARMLESS THE
-- UNITED STATES GOVERNMENT, ITS CONTRACTORS AND SUBCONTRACTORS, AS WELL AS ANY
-- PRIOR RECIPIENT, TO THE EXTENT PERMITTED BY LAW. RECIPIENT'S SOLE REMEDY
-- FOR ANY SUCH MATTER SHALL BE THE IMMEDIATE, UNILATERAL TERMINATION OF THIS
-- AGREEMENT.
--
-- | Abstract representation of an Ogma specification.
module Data.OgmaSpec where

-- | Abstract representation of an Ogma specification.
data Spec a = Spec
    { forall a. Spec a -> [InternalVariableDef]
internalVariables :: [ InternalVariableDef ]
    , forall a. Spec a -> [ExternalVariableDef]
externalVariables :: [ ExternalVariableDef ]
    , forall a. Spec a -> [Requirement a]
requirements      :: [ Requirement a ]
    }
  deriving (Int -> Spec a -> ShowS
[Spec a] -> ShowS
Spec a -> String
(Int -> Spec a -> ShowS)
-> (Spec a -> String) -> ([Spec a] -> ShowS) -> Show (Spec a)
forall a. Show a => Int -> Spec a -> ShowS
forall a. Show a => [Spec a] -> ShowS
forall a. Show a => Spec a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> Spec a -> ShowS
showsPrec :: Int -> Spec a -> ShowS
$cshow :: forall a. Show a => Spec a -> String
show :: Spec a -> String
$cshowList :: forall a. Show a => [Spec a] -> ShowS
showList :: [Spec a] -> ShowS
Show)

-- | Internal variable definition, with a given name, its type and definining
-- expression.
data InternalVariableDef = InternalVariableDef
    { InternalVariableDef -> String
internalVariableName    :: String
    , InternalVariableDef -> String
internalVariableType    :: String
    , InternalVariableDef -> String
internalVariableExpr    :: String
    }
  deriving (Int -> InternalVariableDef -> ShowS
[InternalVariableDef] -> ShowS
InternalVariableDef -> String
(Int -> InternalVariableDef -> ShowS)
-> (InternalVariableDef -> String)
-> ([InternalVariableDef] -> ShowS)
-> Show InternalVariableDef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InternalVariableDef -> ShowS
showsPrec :: Int -> InternalVariableDef -> ShowS
$cshow :: InternalVariableDef -> String
show :: InternalVariableDef -> String
$cshowList :: [InternalVariableDef] -> ShowS
showList :: [InternalVariableDef] -> ShowS
Show)

-- | External variable definition, with a given name and type.
--
-- The value of external variables is assigned outside Copilot, so they have no
-- defining expression in this type.
data ExternalVariableDef = ExternalVariableDef
    { ExternalVariableDef -> String
externalVariableName :: String
    , ExternalVariableDef -> String
externalVariableType :: String
    }
  deriving (Int -> ExternalVariableDef -> ShowS
[ExternalVariableDef] -> ShowS
ExternalVariableDef -> String
(Int -> ExternalVariableDef -> ShowS)
-> (ExternalVariableDef -> String)
-> ([ExternalVariableDef] -> ShowS)
-> Show ExternalVariableDef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExternalVariableDef -> ShowS
showsPrec :: Int -> ExternalVariableDef -> ShowS
$cshow :: ExternalVariableDef -> String
show :: ExternalVariableDef -> String
$cshowList :: [ExternalVariableDef] -> ShowS
showList :: [ExternalVariableDef] -> ShowS
Show)

-- | Requirement with a given name and a boolean expression.
data Requirement a = Requirement
    { forall a. Requirement a -> String
requirementName        :: String
    , forall a. Requirement a -> a
requirementExpr        :: a
    , forall a. Requirement a -> String
requirementDescription :: String
    }
  deriving (Int -> Requirement a -> ShowS
[Requirement a] -> ShowS
Requirement a -> String
(Int -> Requirement a -> ShowS)
-> (Requirement a -> String)
-> ([Requirement a] -> ShowS)
-> Show (Requirement a)
forall a. Show a => Int -> Requirement a -> ShowS
forall a. Show a => [Requirement a] -> ShowS
forall a. Show a => Requirement a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> Requirement a -> ShowS
showsPrec :: Int -> Requirement a -> ShowS
$cshow :: forall a. Show a => Requirement a -> String
show :: Requirement a -> String
$cshowList :: forall a. Show a => [Requirement a] -> ShowS
showList :: [Requirement a] -> ShowS
Show)