1
+ {-# LANGUAGE ExistentialQuantification #-}
1
2
-- Copyright 2020 United States Government as represented by the Administrator
2
3
-- of the National Aeronautics and Space Administration. All Rights Reserved.
3
4
--
@@ -41,7 +42,8 @@ module Command.FRETComponentSpec2Copilot
41
42
42
43
-- External imports
43
44
import Control.Monad.IfElse ( awhen )
44
- import Data.Aeson ( eitherDecode )
45
+ import Data.Aeson ( eitherDecode , decode )
46
+ import Data.ByteString.Lazy (fromStrict )
45
47
46
48
-- External imports: auxiliary
47
49
import Data.ByteString.Extra as B ( safeReadFile )
@@ -50,12 +52,22 @@ import Data.ByteString.Extra as B ( safeReadFile )
50
52
import Command.Result ( Result (.. ) )
51
53
import Data.Location ( Location (.. ) )
52
54
53
- -- Internal imports
54
- import Language.FRETComponentSpec.AST ( FRETComponentSpec )
55
- import qualified Language.Trans.FRETComponentSpec2Copilot as T
56
- ( fretComponentSpec2Copilot
57
- , FRETComponentSpec2CopilotOptions (FRETComponentSpec2CopilotOptions )
58
- )
55
+ -- Internal imports: language ASTs, transformers
56
+ import Data.OgmaSpec (Spec )
57
+
58
+ import qualified Language.CoCoSpec.AbsCoCoSpec as CoCoSpec
59
+ import qualified Language.CoCoSpec.ParCoCoSpec as CoCoSpec ( myLexer ,
60
+ pBoolSpec )
61
+
62
+ import Language.JSONSpec.Parser (JSONFormat (.. ), parseJSONSpec )
63
+
64
+ import qualified Language.SMV.AbsSMV as SMV
65
+ import qualified Language.SMV.ParSMV as SMV (myLexer , pBoolSpec )
66
+ import Language.SMV.Substitution (substituteBoolExpr )
67
+
68
+ import qualified Language.Trans.CoCoSpec2Copilot as CoCoSpec (boolSpec2Copilot )
69
+ import Language.Trans.SMV2Copilot as SMV (boolSpec2Copilot )
70
+ import Language.Trans.Spec2Copilot (spec2Copilot , specAnalyze )
59
71
60
72
-- | Print the contents of a Copilot module that implements the Past-time TL
61
73
-- formula in a FRET file.
@@ -72,22 +84,44 @@ fretComponentSpec2Copilot :: FilePath -- ^ Path to a file containing a FRET
72
84
-> IO (Result ErrorCode )
73
85
fretComponentSpec2Copilot fp options = do
74
86
75
- -- All of the following operations use Either to return error messages. The
76
- -- use of the monadic bind to pass arguments from one function to the next
77
- -- will cause the program to stop at the earliest error.
78
- fret <- parseFretComponentSpec fp
87
+ let functions = fretExprPair (fretCS2CopilotUseCoCoSpec options)
79
88
80
- -- Extract internal command options from external command options
81
- let internalOptions = fretComponentSpec2CopilotOptions options
82
-
83
- let copilot = T. fretComponentSpec2Copilot internalOptions =<< fret
89
+ copilot <- fretComponentSpec2Copilot' fp options functions
84
90
85
91
let (mOutput, result) =
86
92
fretComponentSpec2CopilotResult options fp copilot
87
93
88
94
awhen mOutput putStrLn
89
95
return result
90
96
97
+ -- | Print the contents of a Copilot module that implements the Past-time TL
98
+ -- formula in a FRET file, using a subexpression handler.
99
+ --
100
+ -- PRE: The file given is readable, contains a valid FRET file with a PT
101
+ -- formula in the @ptExpanded@ key, the formula does not use any identifiers
102
+ -- that exist in Copilot, or any of @prop@, @clock@, @ftp@. All identifiers
103
+ -- used are valid C99 identifiers.
104
+ fretComponentSpec2Copilot' :: FilePath
105
+ -> FRETComponentSpec2CopilotOptions
106
+ -> FRETExprPair
107
+ -> IO (Either String String )
108
+ fretComponentSpec2Copilot' fp options (FRETExprPair parse replace print ) = do
109
+ let name = fretCS2CopilotFilename options
110
+ useCoCoSpec = fretCS2CopilotUseCoCoSpec options
111
+ typeMaps = fretTypeToCopilotTypeMapping options
112
+
113
+ -- All of the following operations use Either to return error messages. The
114
+ -- use of the monadic bind to pass arguments from one function to the next
115
+ -- will cause the program to stop at the earliest error.
116
+ content <- B. safeReadFile fp
117
+ res <- case content of
118
+ Left s -> return $ Left s
119
+ Right b -> return $ parseJSONSpec parse (fretFormat useCoCoSpec) =<< eitherDecode b
120
+
121
+ let copilot = spec2Copilot name typeMaps replace print =<< specAnalyze =<< res
122
+
123
+ return copilot
124
+
91
125
-- | Options used to customize the conversion of FRET Component Specifications
92
126
-- to Copilot code.
93
127
data FRETComponentSpec2CopilotOptions = FRETComponentSpec2CopilotOptions
@@ -97,17 +131,6 @@ data FRETComponentSpec2CopilotOptions = FRETComponentSpec2CopilotOptions
97
131
, fretCS2CopilotFilename :: String
98
132
}
99
133
100
- -- | Parse a JSON file containing a FRET component specification.
101
- --
102
- -- Returns a 'Left' with an error message if the file does not have the correct
103
- -- format.
104
- --
105
- -- Throws an exception if the file cannot be read.
106
- parseFretComponentSpec :: FilePath -> IO (Either String FRETComponentSpec )
107
- parseFretComponentSpec fp = do
108
- content <- B. safeReadFile fp
109
- return $ eitherDecode =<< content
110
-
111
134
-- * Error codes
112
135
113
136
-- | Encoding of reasons why the command can fail.
@@ -120,19 +143,6 @@ type ErrorCode = Int
120
143
ecFretCSError :: ErrorCode
121
144
ecFretCSError = 1
122
145
123
- -- * Input arguments
124
-
125
- -- | Convert command input argument options to internal transformation function
126
- -- input arguments.
127
- fretComponentSpec2CopilotOptions :: FRETComponentSpec2CopilotOptions
128
- -> T. FRETComponentSpec2CopilotOptions
129
- fretComponentSpec2CopilotOptions options =
130
- T. FRETComponentSpec2CopilotOptions
131
- (fretCS2CopilotUseCoCoSpec options)
132
- (fretCS2CopilotIntType options)
133
- (fretCS2CopilotRealType options)
134
- (fretCS2CopilotFilename options)
135
-
136
146
-- * Result
137
147
138
148
-- | Process the result of the transformation function.
@@ -143,3 +153,52 @@ fretComponentSpec2CopilotResult :: FRETComponentSpec2CopilotOptions
143
153
fretComponentSpec2CopilotResult options fp result = case result of
144
154
Left msg -> (Nothing , Error ecFretCSError msg (LocationFile fp))
145
155
Right t -> (Just t, Success )
156
+
157
+ -- * Parser
158
+
159
+ -- | JSONPath selectors for a FRET file
160
+ fretFormat :: Bool -> JSONFormat
161
+ fretFormat useCoCoSpec = JSONFormat
162
+ { specInternalVars = " ..Internal_variables[*]"
163
+ , specInternalVarId = " .name"
164
+ , specInternalVarExpr = " .assignmentCopilot"
165
+ , specInternalVarType = " .type"
166
+ , specExternalVars = " ..Other_variables[*]"
167
+ , specExternalVarId = " .name"
168
+ , specExternalVarType = " .type"
169
+ , specRequirements = " ..Requirements[*]"
170
+ , specRequirementId = " .name"
171
+ , specRequirementDesc = " .fretish"
172
+ , specRequirementExpr = if useCoCoSpec then " .CoCoSpecCode" else " .ptLTL"
173
+ }
174
+
175
+ -- * Mapping of types from FRET to Copilot
176
+ fretTypeToCopilotTypeMapping :: FRETComponentSpec2CopilotOptions
177
+ -> [(String , String )]
178
+ fretTypeToCopilotTypeMapping options =
179
+ [ (" bool" , " Bool" )
180
+ , (" int" , fretCS2CopilotIntType options)
181
+ , (" integer" , fretCS2CopilotIntType options)
182
+ , (" real" , fretCS2CopilotRealType options)
183
+ , (" string" , " String" )
184
+ ]
185
+
186
+ -- * Handler for boolean expressions
187
+
188
+ -- | Handler for boolean expressions that knows how to parse them, replace
189
+ -- variables in them, and convert them to Copilot.
190
+ data FRETExprPair = forall a . FRETExprPair
191
+ { exprParse :: String -> Either String a
192
+ , exprReplace :: [(String , String )] -> a -> a
193
+ , exprPrint :: a -> String
194
+ }
195
+
196
+ -- | Return a handler depending on whether it should be for CoCoSpec boolean
197
+ -- expressions or for SMV boolean expressions.
198
+ fretExprPair :: Bool -> FRETExprPair
199
+ fretExprPair True = FRETExprPair (CoCoSpec. pBoolSpec . CoCoSpec. myLexer)
200
+ (\ _ -> id )
201
+ (CoCoSpec. boolSpec2Copilot)
202
+ fretExprPair False = FRETExprPair (SMV. pBoolSpec . SMV. myLexer)
203
+ (substituteBoolExpr)
204
+ (SMV. boolSpec2Copilot)
0 commit comments