{-# LANGUAGE TemplateHaskell, TupleSections #-}
module Drasil.GOOL.State (
GS, GOOLState(..), FS, CS, MS, VS,
lensFStoGS, lensGStoFS, lensMStoGS, lensFStoCS, lensFStoMS, lensFStoVS,
lensCStoMS, lensMStoCS, lensCStoVS, lensMStoFS, lensMStoVS, lensVStoFS,
lensVStoMS, lensCStoFS, headers, sources, mainMod, currMain, currFileType, currParameters,
initialState, initialFS,
modifyReturn, modifyReturnFunc, modifyReturnList,
revFiles, addFile, addCombinedHeaderSource, addHeader, addSource,
addProgNameToPaths, setMainMod, addLangImport, addLangImportVS,
addExceptionImports, getLangImports, addLibImport, addLibImportVS,
addLibImports, getLibImports, addModuleImport, addModuleImportVS,
getModuleImports, addHeaderLangImport, getHeaderLangImports,
addHeaderLibImport, getHeaderLibImports, addHeaderModImport,
getHeaderModImports, addDefine, getDefines, addHeaderDefine,
getHeaderDefines, addUsing, getUsing, addHeaderUsing, getHeaderUsing,
setFileType, setModuleName, getModuleName, setClassName, getClassName,
setCurrMain, getCurrMain, addClass, getClasses, updateClassMap, getClassMap,
updateMethodExcMap, getMethodExcMap, updateCallMap, callMapTransClosure,
updateMEMWithCalls, addParameter, getParameters, setOutputsDeclared,
isOutputsDeclared, addException, addExceptions, getExceptions, addCall,
setMainDoc, getMainDoc, setVisibility, getVisibility, setCurrMainFunc,
getCurrMainFunc, setThrowUsed, getThrowUsed, setErrorDefined, getErrorDefined,
incrementLine, incrementWord, getLineIndex,
getWordIndex, resetIndices, useVarName, genVarName, genLoopIndex,
genVarNameIf, varNameAvailable, setVarScope, getVarScope
) where
import Drasil.GOOL.AST (FileType(..), VisibilityTag(..), ScopeTag(..),
ScopeData(..), sd, QualifiedName, qualName)
import Drasil.GOOL.CodeAnalysis (Exception, ExceptionType, printExc, hasLoc)
import Drasil.GOOL.CodeType (ClassName)
import Utils.Drasil (nubSort)
import Control.Lens (Lens', (^.), lens, makeLenses, over, set, _1, _2, both, at)
import Control.Monad.State (State, modify, gets)
import Data.Char (isDigit)
import Data.List (nub)
import Data.Foldable (foldl')
import Data.Maybe (isNothing, fromMaybe)
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Tuple (swap)
import Text.PrettyPrint.HughesPJ (Doc, empty)
import Text.Read (readMaybe)
data GOOLState = GS {
:: [FilePath],
GOOLState -> [String]
_sources :: [FilePath],
GOOLState -> Maybe String
_mainMod :: Maybe FilePath,
GOOLState -> Map String String
_classMap :: Map String ClassName,
GOOLState -> Map QualifiedName [ExceptionType]
_methodExceptionMap :: Map QualifiedName [ExceptionType],
GOOLState -> Map QualifiedName [QualifiedName]
_callMap :: Map QualifiedName [QualifiedName],
GOOLState -> Bool
_throwUsed :: Bool,
GOOLState -> Bool
_errorDefined :: Bool
}
data FileState = FS {
FileState -> GOOLState
_goolState :: GOOLState,
FileState -> String
_currModName :: String,
FileState -> FileType
_currFileType :: FileType,
FileState -> Bool
_currMain :: Bool,
FileState -> [String]
_currClasses :: [ClassName],
FileState -> [String]
_langImports :: [String],
FileState -> [String]
_libImports :: [String],
FileState -> [String]
_moduleImports :: [String],
FileState -> Doc
_mainDoc :: Doc,
:: [String],
:: [String],
:: [String],
FileState -> [String]
_defines :: [String],
:: [String],
FileState -> [String]
_using :: [String],
:: [String]
}
data ClassState = CS {
ClassState -> FileState
_fileState :: FileState,
ClassState -> String
_currClassName :: ClassName
}
makeLenses ''ClassState
type Index = Integer
data MethodState = MS {
MethodState -> ClassState
_classState :: ClassState,
MethodState -> [String]
_currParameters :: [String],
MethodState -> Map String Int
_varNames :: Map String Int,
MethodState -> Map String ScopeData
_varScopes :: Map String ScopeData,
MethodState -> Bool
_outputsDeclared :: Bool,
MethodState -> [ExceptionType]
_exceptions :: [ExceptionType],
MethodState -> [QualifiedName]
_calls :: [QualifiedName],
MethodState -> VisibilityTag
_currVisibility :: VisibilityTag,
MethodState -> Bool
_currMainFunc :: Bool,
MethodState -> (Index, Index)
_contentsIndices :: (Index, Index)
}
makeLenses ''MethodState
newtype ValueState = VS {
ValueState -> MethodState
_methodState :: MethodState
}
makeLenses ''ValueState
type GS = State GOOLState
type FS = State FileState
type CS = State ClassState
type MS = State MethodState
type VS = State ValueState
lensGStoFS :: Lens' GOOLState FileState
lensGStoFS :: Lens' GOOLState FileState
lensGStoFS = (GOOLState -> FileState)
-> (GOOLState -> FileState -> GOOLState)
-> Lens' GOOLState FileState
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\GOOLState
gs -> ASetter FileState FileState GOOLState GOOLState
-> GOOLState -> FileState -> FileState
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter FileState FileState GOOLState GOOLState
Lens' FileState GOOLState
goolState GOOLState
gs FileState
initialFS) ((FileState -> GOOLState) -> GOOLState -> FileState -> GOOLState
forall a b. a -> b -> a
const (FileState -> Getting GOOLState FileState GOOLState -> GOOLState
forall s a. s -> Getting a s a -> a
^. Getting GOOLState FileState GOOLState
Lens' FileState GOOLState
goolState))
lensFStoGS :: Lens' FileState GOOLState
lensFStoGS :: Lens' FileState GOOLState
lensFStoGS = (GOOLState -> f GOOLState) -> FileState -> f FileState
Lens' FileState GOOLState
goolState
lensMStoGS :: Lens' MethodState GOOLState
lensMStoGS :: Lens' MethodState GOOLState
lensMStoGS = (FileState -> f FileState) -> MethodState -> f MethodState
Lens' MethodState FileState
lensMStoFS ((FileState -> f FileState) -> MethodState -> f MethodState)
-> ((GOOLState -> f GOOLState) -> FileState -> f FileState)
-> (GOOLState -> f GOOLState)
-> MethodState
-> f MethodState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GOOLState -> f GOOLState) -> FileState -> f FileState
Lens' FileState GOOLState
lensFStoGS
lensFStoCS :: Lens' FileState ClassState
lensFStoCS :: Lens' FileState ClassState
lensFStoCS = (FileState -> ClassState)
-> (FileState -> ClassState -> FileState)
-> Lens' FileState ClassState
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\FileState
fs -> ASetter ClassState ClassState FileState FileState
-> FileState -> ClassState -> ClassState
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter ClassState ClassState FileState FileState
Lens' ClassState FileState
fileState FileState
fs ClassState
initialCS) ((ClassState -> FileState) -> FileState -> ClassState -> FileState
forall a b. a -> b -> a
const (ClassState -> Getting FileState ClassState FileState -> FileState
forall s a. s -> Getting a s a -> a
^. Getting FileState ClassState FileState
Lens' ClassState FileState
fileState))
lensCStoFS :: Lens' ClassState FileState
lensCStoFS :: Lens' ClassState FileState
lensCStoFS = (FileState -> f FileState) -> ClassState -> f ClassState
Lens' ClassState FileState
fileState
lensFStoMS :: Lens' FileState MethodState
lensFStoMS :: Lens' FileState MethodState
lensFStoMS = (FileState -> MethodState)
-> (FileState -> MethodState -> FileState)
-> Lens' FileState MethodState
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\FileState
fs -> ASetter MethodState MethodState FileState FileState
-> FileState -> MethodState -> MethodState
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter MethodState MethodState FileState FileState
Lens' MethodState FileState
lensMStoFS FileState
fs MethodState
initialMS) ((MethodState -> FileState) -> FileState -> MethodState -> FileState
forall a b. a -> b -> a
const (MethodState -> Getting FileState MethodState FileState -> FileState
forall s a. s -> Getting a s a -> a
^. Getting FileState MethodState FileState
Lens' MethodState FileState
lensMStoFS))
lensMStoFS :: Lens' MethodState FileState
lensMStoFS :: Lens' MethodState FileState
lensMStoFS = (ClassState -> f ClassState) -> MethodState -> f MethodState
Lens' MethodState ClassState
classState ((ClassState -> f ClassState) -> MethodState -> f MethodState)
-> ((FileState -> f FileState) -> ClassState -> f ClassState)
-> (FileState -> f FileState)
-> MethodState
-> f MethodState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FileState -> f FileState) -> ClassState -> f ClassState
Lens' ClassState FileState
fileState
lensCStoMS :: Lens' ClassState MethodState
lensCStoMS :: Lens' ClassState MethodState
lensCStoMS = (ClassState -> MethodState)
-> (ClassState -> MethodState -> ClassState)
-> Lens' ClassState MethodState
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\ClassState
cs -> ASetter MethodState MethodState ClassState ClassState
-> ClassState -> MethodState -> MethodState
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter MethodState MethodState ClassState ClassState
Lens' MethodState ClassState
classState ClassState
cs MethodState
initialMS) ((MethodState -> ClassState)
-> ClassState -> MethodState -> ClassState
forall a b. a -> b -> a
const (MethodState
-> Getting ClassState MethodState ClassState -> ClassState
forall s a. s -> Getting a s a -> a
^. Getting ClassState MethodState ClassState
Lens' MethodState ClassState
classState))
lensMStoCS :: Lens' MethodState ClassState
lensMStoCS :: Lens' MethodState ClassState
lensMStoCS = (ClassState -> f ClassState) -> MethodState -> f MethodState
Lens' MethodState ClassState
classState
lensFStoVS :: Lens' FileState ValueState
lensFStoVS :: Lens' FileState ValueState
lensFStoVS = (FileState -> ValueState)
-> (FileState -> ValueState -> FileState)
-> Lens' FileState ValueState
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\FileState
fs -> ASetter ValueState ValueState FileState FileState
-> FileState -> ValueState -> ValueState
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter ValueState ValueState FileState FileState
Lens' ValueState FileState
lensVStoFS FileState
fs ValueState
initialVS) ((ValueState -> FileState) -> FileState -> ValueState -> FileState
forall a b. a -> b -> a
const (ValueState -> Getting FileState ValueState FileState -> FileState
forall s a. s -> Getting a s a -> a
^. Getting FileState ValueState FileState
Lens' ValueState FileState
lensVStoFS))
lensVStoFS :: Lens' ValueState FileState
lensVStoFS :: Lens' ValueState FileState
lensVStoFS = (MethodState -> f MethodState) -> ValueState -> f ValueState
Iso' ValueState MethodState
methodState ((MethodState -> f MethodState) -> ValueState -> f ValueState)
-> ((FileState -> f FileState) -> MethodState -> f MethodState)
-> (FileState -> f FileState)
-> ValueState
-> f ValueState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FileState -> f FileState) -> MethodState -> f MethodState
Lens' MethodState FileState
lensMStoFS
lensCStoVS :: Lens' ClassState ValueState
lensCStoVS :: Lens' ClassState ValueState
lensCStoVS = (ClassState -> ValueState)
-> (ClassState -> ValueState -> ClassState)
-> Lens' ClassState ValueState
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\ClassState
cs -> ASetter ValueState ValueState ClassState ClassState
-> ClassState -> ValueState -> ValueState
forall s t a b. ASetter s t a b -> b -> s -> t
set ((MethodState -> Identity MethodState)
-> ValueState -> Identity ValueState
Iso' ValueState MethodState
methodState ((MethodState -> Identity MethodState)
-> ValueState -> Identity ValueState)
-> ASetter MethodState MethodState ClassState ClassState
-> ASetter ValueState ValueState ClassState ClassState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASetter MethodState MethodState ClassState ClassState
Lens' MethodState ClassState
classState) ClassState
cs ValueState
initialVS)
((ValueState -> ClassState)
-> ClassState -> ValueState -> ClassState
forall a b. a -> b -> a
const (ValueState
-> Getting ClassState ValueState ClassState -> ClassState
forall s a. s -> Getting a s a -> a
^. ((MethodState -> Const ClassState MethodState)
-> ValueState -> Const ClassState ValueState
Iso' ValueState MethodState
methodState ((MethodState -> Const ClassState MethodState)
-> ValueState -> Const ClassState ValueState)
-> Getting ClassState MethodState ClassState
-> Getting ClassState ValueState ClassState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting ClassState MethodState ClassState
Lens' MethodState ClassState
classState)))
lensMStoVS :: Lens' MethodState ValueState
lensMStoVS :: Lens' MethodState ValueState
lensMStoVS = (MethodState -> ValueState)
-> (MethodState -> ValueState -> MethodState)
-> Lens' MethodState ValueState
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\MethodState
ms -> ((MethodState -> Identity MethodState)
-> ValueState -> Identity ValueState)
-> MethodState -> ValueState -> ValueState
forall s t a b. ASetter s t a b -> b -> s -> t
set (MethodState -> Identity MethodState)
-> ValueState -> Identity ValueState
Iso' ValueState MethodState
methodState MethodState
ms ValueState
initialVS) ((ValueState -> MethodState)
-> MethodState -> ValueState -> MethodState
forall a b. a -> b -> a
const (ValueState
-> Getting MethodState ValueState MethodState -> MethodState
forall s a. s -> Getting a s a -> a
^. Getting MethodState ValueState MethodState
Iso' ValueState MethodState
methodState))
lensVStoMS :: Lens' ValueState MethodState
lensVStoMS :: Lens' ValueState MethodState
lensVStoMS = (MethodState -> f MethodState) -> ValueState -> f ValueState
Iso' ValueState MethodState
methodState
initialState :: GOOLState
initialState :: GOOLState
initialState = GS {
_headers :: [String]
_headers = [],
_sources :: [String]
_sources = [],
_mainMod :: Maybe String
_mainMod = Maybe String
forall a. Maybe a
Nothing,
_classMap :: Map String String
_classMap = Map String String
forall k a. Map k a
Map.empty,
_methodExceptionMap :: Map QualifiedName [ExceptionType]
_methodExceptionMap = Map QualifiedName [ExceptionType]
forall k a. Map k a
Map.empty,
_callMap :: Map QualifiedName [QualifiedName]
_callMap = Map QualifiedName [QualifiedName]
forall k a. Map k a
Map.empty,
_throwUsed :: Bool
_throwUsed = Bool
False,
_errorDefined :: Bool
_errorDefined = Bool
False
}
initialFS :: FileState
initialFS :: FileState
initialFS = FS {
_goolState :: GOOLState
_goolState = GOOLState
initialState,
_currModName :: String
_currModName = String
"",
_currFileType :: FileType
_currFileType = FileType
Combined,
_currMain :: Bool
_currMain = Bool
False,
_currClasses :: [String]
_currClasses = [],
_langImports :: [String]
_langImports = [],
_libImports :: [String]
_libImports = [],
_moduleImports :: [String]
_moduleImports = [],
_mainDoc :: Doc
_mainDoc = Doc
empty,
_headerLangImports :: [String]
_headerLangImports = [],
_headerLibImports :: [String]
_headerLibImports = [],
_headerModImports :: [String]
_headerModImports = [],
_defines :: [String]
_defines = [],
_headerDefines :: [String]
_headerDefines = [],
_using :: [String]
_using = [],
_headerUsing :: [String]
_headerUsing = []
}
initialCS :: ClassState
initialCS :: ClassState
initialCS = CS {
_fileState :: FileState
_fileState = FileState
initialFS,
_currClassName :: String
_currClassName = String
""
}
initialMS :: MethodState
initialMS :: MethodState
initialMS = MS {
_classState :: ClassState
_classState = ClassState
initialCS,
_currParameters :: [String]
_currParameters = [],
_varNames :: Map String Int
_varNames = Map String Int
forall k a. Map k a
Map.empty,
_varScopes :: Map String ScopeData
_varScopes = [(String, ScopeData)] -> Map String ScopeData
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(String
"", ScopeTag -> ScopeData
sd ScopeTag
Local)],
_outputsDeclared :: Bool
_outputsDeclared = Bool
False,
_exceptions :: [ExceptionType]
_exceptions = [],
_calls :: [QualifiedName]
_calls = [],
_currVisibility :: VisibilityTag
_currVisibility = VisibilityTag
Priv,
_currMainFunc :: Bool
_currMainFunc = Bool
False,
_contentsIndices :: (Index, Index)
_contentsIndices = (Index
0,Index
0)
}
initialVS :: ValueState
initialVS :: ValueState
initialVS = VS {
_methodState :: MethodState
_methodState = MethodState
initialMS
}
modifyReturn :: (s -> s) -> a -> State s a
modifyReturn :: forall s a. (s -> s) -> a -> State s a
modifyReturn s -> s
sf a
v = do
(s -> s) -> StateT s Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify s -> s
sf
a -> State s a
forall a. a -> StateT s Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return a
v
modifyReturnFunc :: (b -> s -> s) -> (b -> a) -> State s b -> State s a
modifyReturnFunc :: forall b s a. (b -> s -> s) -> (b -> a) -> State s b -> State s a
modifyReturnFunc b -> s -> s
sf b -> a
vf State s b
st = do
b
v <- State s b
st
(s -> s) -> StateT s Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((s -> s) -> StateT s Identity ())
-> (s -> s) -> StateT s Identity ()
forall a b. (a -> b) -> a -> b
$ b -> s -> s
sf b
v
a -> State s a
forall a. a -> StateT s Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> State s a) -> a -> State s a
forall a b. (a -> b) -> a -> b
$ b -> a
vf b
v
modifyReturnList :: [State s b] -> (s -> s) ->
([b] -> a) -> State s a
modifyReturnList :: forall s b a. [State s b] -> (s -> s) -> ([b] -> a) -> State s a
modifyReturnList [State s b]
l s -> s
sf [b] -> a
vf = do
[b]
v <- [State s b] -> StateT s Identity [b]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence [State s b]
l
(s -> s) -> StateT s Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify s -> s
sf
a -> State s a
forall a. a -> StateT s Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> State s a) -> a -> State s a
forall a b. (a -> b) -> a -> b
$ [b] -> a
vf [b]
v
revFiles :: GOOLState -> GOOLState
revFiles :: GOOLState -> GOOLState
revFiles = ASetter GOOLState GOOLState [String] [String]
-> ([String] -> [String]) -> GOOLState -> GOOLState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter GOOLState GOOLState [String] [String]
Lens' GOOLState [String]
headers [String] -> [String]
forall a. [a] -> [a]
reverse (GOOLState -> GOOLState)
-> (GOOLState -> GOOLState) -> GOOLState -> GOOLState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASetter GOOLState GOOLState [String] [String]
-> ([String] -> [String]) -> GOOLState -> GOOLState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter GOOLState GOOLState [String] [String]
Lens' GOOLState [String]
sources [String] -> [String]
forall a. [a] -> [a]
reverse
addFile :: FileType -> FilePath -> GOOLState -> GOOLState
addFile :: FileType -> String -> GOOLState -> GOOLState
addFile FileType
Combined = String -> GOOLState -> GOOLState
addCombinedHeaderSource
addFile FileType
Source = String -> GOOLState -> GOOLState
addSource
addFile FileType
Header = String -> GOOLState -> GOOLState
addHeader
addHeader :: FilePath -> GOOLState -> GOOLState
String
fp = ASetter GOOLState GOOLState [String] [String]
-> ([String] -> [String]) -> GOOLState -> GOOLState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter GOOLState GOOLState [String] [String]
Lens' GOOLState [String]
headers (\[String]
h -> String -> [String] -> String -> [String]
forall a. Eq a => a -> [a] -> String -> [a]
ifElemError String
fp [String]
h (String -> [String]) -> String -> [String]
forall a b. (a -> b) -> a -> b
$
String
"Multiple files with same name encountered: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fp)
addSource :: FilePath -> GOOLState -> GOOLState
addSource :: String -> GOOLState -> GOOLState
addSource String
fp = ASetter GOOLState GOOLState [String] [String]
-> ([String] -> [String]) -> GOOLState -> GOOLState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter GOOLState GOOLState [String] [String]
Lens' GOOLState [String]
sources (\[String]
s -> String -> [String] -> String -> [String]
forall a. Eq a => a -> [a] -> String -> [a]
ifElemError String
fp [String]
s (String -> [String]) -> String -> [String]
forall a b. (a -> b) -> a -> b
$
String
"Multiple files with same name encountered: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fp)
addCombinedHeaderSource :: FilePath -> GOOLState -> GOOLState
String
fp = String -> GOOLState -> GOOLState
addSource String
fp (GOOLState -> GOOLState)
-> (GOOLState -> GOOLState) -> GOOLState -> GOOLState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> GOOLState -> GOOLState
addHeader String
fp
addProgNameToPaths :: String -> GOOLState -> GOOLState
addProgNameToPaths :: String -> GOOLState -> GOOLState
addProgNameToPaths String
n = ASetter GOOLState GOOLState (Maybe String) (Maybe String)
-> (Maybe String -> Maybe String) -> GOOLState -> GOOLState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter GOOLState GOOLState (Maybe String) (Maybe String)
Lens' GOOLState (Maybe String)
mainMod ((String -> String) -> Maybe String -> Maybe String
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> String
f) (GOOLState -> GOOLState)
-> (GOOLState -> GOOLState) -> GOOLState -> GOOLState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASetter GOOLState GOOLState [String] [String]
-> ([String] -> [String]) -> GOOLState -> GOOLState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter GOOLState GOOLState [String] [String]
Lens' GOOLState [String]
sources ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
f) (GOOLState -> GOOLState)
-> (GOOLState -> GOOLState) -> GOOLState -> GOOLState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ASetter GOOLState GOOLState [String] [String]
-> ([String] -> [String]) -> GOOLState -> GOOLState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter GOOLState GOOLState [String] [String]
Lens' GOOLState [String]
headers ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
f)
where f :: String -> String
f = ((String
nString -> String -> String
forall a. [a] -> [a] -> [a]
++String
"/")String -> String -> String
forall a. [a] -> [a] -> [a]
++)
setMainMod :: String -> GOOLState -> GOOLState
setMainMod :: String -> GOOLState -> GOOLState
setMainMod String
n = ASetter GOOLState GOOLState (Maybe String) (Maybe String)
-> (Maybe String -> Maybe String) -> GOOLState -> GOOLState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter GOOLState GOOLState (Maybe String) (Maybe String)
Lens' GOOLState (Maybe String)
mainMod (\Maybe String
m -> if Maybe String -> Bool
forall a. Maybe a -> Bool
isNothing Maybe String
m then String -> Maybe String
forall a. a -> Maybe a
Just String
n else String -> Maybe String
forall a. HasCallStack => String -> a
error
String
"Multiple modules with main methods encountered")
addLangImport :: String -> MethodState -> MethodState
addLangImport :: String -> MethodState -> MethodState
addLangImport String
i = ASetter MethodState MethodState [String] [String]
-> ([String] -> [String]) -> MethodState -> MethodState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (ASetter MethodState MethodState FileState FileState
Lens' MethodState FileState
lensMStoFS ASetter MethodState MethodState FileState FileState
-> (([String] -> Identity [String])
-> FileState -> Identity FileState)
-> ASetter MethodState MethodState [String] [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([String] -> Identity [String]) -> FileState -> Identity FileState
Lens' FileState [String]
langImports) (\[String]
is -> [String] -> [String]
forall a. Ord a => [a] -> [a]
nubSort ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String
iString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
is)
addLangImportVS :: String -> ValueState -> ValueState
addLangImportVS :: String -> ValueState -> ValueState
addLangImportVS String
i = ((MethodState -> Identity MethodState)
-> ValueState -> Identity ValueState)
-> (MethodState -> MethodState) -> ValueState -> ValueState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (MethodState -> Identity MethodState)
-> ValueState -> Identity ValueState
Iso' ValueState MethodState
methodState (String -> MethodState -> MethodState
addLangImport String
i)
addExceptionImports :: [Exception] -> MethodState -> MethodState
addExceptionImports :: [Exception] -> MethodState -> MethodState
addExceptionImports [Exception]
es = ASetter MethodState MethodState [String] [String]
-> ([String] -> [String]) -> MethodState -> MethodState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (ASetter MethodState MethodState FileState FileState
Lens' MethodState FileState
lensMStoFS ASetter MethodState MethodState FileState FileState
-> (([String] -> Identity [String])
-> FileState -> Identity FileState)
-> ASetter MethodState MethodState [String] [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([String] -> Identity [String]) -> FileState -> Identity FileState
Lens' FileState [String]
langImports)
(\[String]
is -> [String] -> [String]
forall a. Ord a => [a] -> [a]
nubSort ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
is [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
imps)
where imps :: [String]
imps = (Exception -> String) -> [Exception] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Exception -> String
printExc ([Exception] -> [String]) -> [Exception] -> [String]
forall a b. (a -> b) -> a -> b
$ (Exception -> Bool) -> [Exception] -> [Exception]
forall a. (a -> Bool) -> [a] -> [a]
filter Exception -> Bool
hasLoc [Exception]
es
getLangImports :: FS [String]
getLangImports :: FS [String]
getLangImports = (FileState -> [String]) -> FS [String]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (FileState -> Getting [String] FileState [String] -> [String]
forall s a. s -> Getting a s a -> a
^. Getting [String] FileState [String]
Lens' FileState [String]
langImports)
addLibImport :: String -> MethodState -> MethodState
addLibImport :: String -> MethodState -> MethodState
addLibImport String
i = ASetter MethodState MethodState [String] [String]
-> ([String] -> [String]) -> MethodState -> MethodState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (ASetter MethodState MethodState FileState FileState
Lens' MethodState FileState
lensMStoFS ASetter MethodState MethodState FileState FileState
-> (([String] -> Identity [String])
-> FileState -> Identity FileState)
-> ASetter MethodState MethodState [String] [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([String] -> Identity [String]) -> FileState -> Identity FileState
Lens' FileState [String]
libImports) (\[String]
is -> [String] -> [String]
forall a. Ord a => [a] -> [a]
nubSort ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String
iString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
is)
addLibImportVS :: String -> ValueState -> ValueState
addLibImportVS :: String -> ValueState -> ValueState
addLibImportVS String
i = ASetter ValueState ValueState [String] [String]
-> ([String] -> [String]) -> ValueState -> ValueState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (ASetter ValueState ValueState FileState FileState
Lens' ValueState FileState
lensVStoFS ASetter ValueState ValueState FileState FileState
-> (([String] -> Identity [String])
-> FileState -> Identity FileState)
-> ASetter ValueState ValueState [String] [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([String] -> Identity [String]) -> FileState -> Identity FileState
Lens' FileState [String]
libImports) (\[String]
is -> [String] -> [String]
forall a. Ord a => [a] -> [a]
nubSort ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String
iString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
is)
addLibImports :: [String] -> MethodState -> MethodState
addLibImports :: [String] -> MethodState -> MethodState
addLibImports [String]
is MethodState
s = (MethodState -> String -> MethodState)
-> MethodState -> [String] -> MethodState
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' ((String -> MethodState -> MethodState)
-> MethodState -> String -> MethodState
forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> MethodState -> MethodState
addLibImport) MethodState
s [String]
is
getLibImports :: FS [String]
getLibImports :: FS [String]
getLibImports = (FileState -> [String]) -> FS [String]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (FileState -> Getting [String] FileState [String] -> [String]
forall s a. s -> Getting a s a -> a
^. Getting [String] FileState [String]
Lens' FileState [String]
libImports)
addModuleImport :: String -> MethodState -> MethodState
addModuleImport :: String -> MethodState -> MethodState
addModuleImport String
i = ASetter MethodState MethodState [String] [String]
-> ([String] -> [String]) -> MethodState -> MethodState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (ASetter MethodState MethodState FileState FileState
Lens' MethodState FileState
lensMStoFS ASetter MethodState MethodState FileState FileState
-> (([String] -> Identity [String])
-> FileState -> Identity FileState)
-> ASetter MethodState MethodState [String] [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([String] -> Identity [String]) -> FileState -> Identity FileState
Lens' FileState [String]
moduleImports) (\[String]
is -> [String] -> [String]
forall a. Ord a => [a] -> [a]
nubSort ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String
iString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
is)
addModuleImportVS :: String -> ValueState -> ValueState
addModuleImportVS :: String -> ValueState -> ValueState
addModuleImportVS String
i = ((MethodState -> Identity MethodState)
-> ValueState -> Identity ValueState)
-> (MethodState -> MethodState) -> ValueState -> ValueState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (MethodState -> Identity MethodState)
-> ValueState -> Identity ValueState
Iso' ValueState MethodState
methodState (String -> MethodState -> MethodState
addModuleImport String
i)
getModuleImports :: FS [String]
getModuleImports :: FS [String]
getModuleImports = (FileState -> [String]) -> FS [String]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (FileState -> Getting [String] FileState [String] -> [String]
forall s a. s -> Getting a s a -> a
^. Getting [String] FileState [String]
Lens' FileState [String]
moduleImports)
addHeaderLangImport :: String -> ValueState -> ValueState
String
i = ASetter ValueState ValueState [String] [String]
-> ([String] -> [String]) -> ValueState -> ValueState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (ASetter ValueState ValueState FileState FileState
Lens' ValueState FileState
lensVStoFS ASetter ValueState ValueState FileState FileState
-> (([String] -> Identity [String])
-> FileState -> Identity FileState)
-> ASetter ValueState ValueState [String] [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([String] -> Identity [String]) -> FileState -> Identity FileState
Lens' FileState [String]
headerLangImports)
(\[String]
is -> [String] -> [String]
forall a. Ord a => [a] -> [a]
nubSort ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String
iString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
is)
getHeaderLangImports :: FS [String]
= (FileState -> [String]) -> FS [String]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (FileState -> Getting [String] FileState [String] -> [String]
forall s a. s -> Getting a s a -> a
^. Getting [String] FileState [String]
Lens' FileState [String]
headerLangImports)
addHeaderLibImport :: String -> MethodState -> MethodState
String
i = ASetter MethodState MethodState [String] [String]
-> ([String] -> [String]) -> MethodState -> MethodState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (ASetter MethodState MethodState FileState FileState
Lens' MethodState FileState
lensMStoFS ASetter MethodState MethodState FileState FileState
-> (([String] -> Identity [String])
-> FileState -> Identity FileState)
-> ASetter MethodState MethodState [String] [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([String] -> Identity [String]) -> FileState -> Identity FileState
Lens' FileState [String]
headerLibImports)
(\[String]
is -> [String] -> [String]
forall a. Ord a => [a] -> [a]
nubSort ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String
iString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
is)
getHeaderLibImports :: FS [String]
= (FileState -> [String]) -> FS [String]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (FileState -> Getting [String] FileState [String] -> [String]
forall s a. s -> Getting a s a -> a
^. Getting [String] FileState [String]
Lens' FileState [String]
headerLibImports)
addHeaderModImport :: String -> ValueState -> ValueState
String
i = ASetter ValueState ValueState [String] [String]
-> ([String] -> [String]) -> ValueState -> ValueState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (ASetter ValueState ValueState FileState FileState
Lens' ValueState FileState
lensVStoFS ASetter ValueState ValueState FileState FileState
-> (([String] -> Identity [String])
-> FileState -> Identity FileState)
-> ASetter ValueState ValueState [String] [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([String] -> Identity [String]) -> FileState -> Identity FileState
Lens' FileState [String]
headerModImports)
(\[String]
is -> [String] -> [String]
forall a. Ord a => [a] -> [a]
nubSort ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String
iString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
is)
getHeaderModImports :: FS [String]
= (FileState -> [String]) -> FS [String]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (FileState -> Getting [String] FileState [String] -> [String]
forall s a. s -> Getting a s a -> a
^. Getting [String] FileState [String]
Lens' FileState [String]
headerModImports)
addDefine :: String -> ValueState -> ValueState
addDefine :: String -> ValueState -> ValueState
addDefine String
d = ASetter ValueState ValueState [String] [String]
-> ([String] -> [String]) -> ValueState -> ValueState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (ASetter ValueState ValueState FileState FileState
Lens' ValueState FileState
lensVStoFS ASetter ValueState ValueState FileState FileState
-> (([String] -> Identity [String])
-> FileState -> Identity FileState)
-> ASetter ValueState ValueState [String] [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([String] -> Identity [String]) -> FileState -> Identity FileState
Lens' FileState [String]
defines) (\[String]
ds -> [String] -> [String]
forall a. Ord a => [a] -> [a]
nubSort ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String
dString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
ds)
getDefines :: FS [String]
getDefines :: FS [String]
getDefines = (FileState -> [String]) -> FS [String]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (FileState -> Getting [String] FileState [String] -> [String]
forall s a. s -> Getting a s a -> a
^. Getting [String] FileState [String]
Lens' FileState [String]
defines)
addHeaderDefine :: String -> ValueState -> ValueState
String
d = ASetter ValueState ValueState [String] [String]
-> ([String] -> [String]) -> ValueState -> ValueState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (ASetter ValueState ValueState FileState FileState
Lens' ValueState FileState
lensVStoFS ASetter ValueState ValueState FileState FileState
-> (([String] -> Identity [String])
-> FileState -> Identity FileState)
-> ASetter ValueState ValueState [String] [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([String] -> Identity [String]) -> FileState -> Identity FileState
Lens' FileState [String]
headerDefines) (\[String]
ds -> [String] -> [String]
forall a. Ord a => [a] -> [a]
nubSort ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String
dString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
ds)
getHeaderDefines :: FS [String]
= (FileState -> [String]) -> FS [String]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (FileState -> Getting [String] FileState [String] -> [String]
forall s a. s -> Getting a s a -> a
^. Getting [String] FileState [String]
Lens' FileState [String]
headerDefines)
addUsing :: String -> ValueState -> ValueState
addUsing :: String -> ValueState -> ValueState
addUsing String
u = ASetter ValueState ValueState [String] [String]
-> ([String] -> [String]) -> ValueState -> ValueState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (ASetter ValueState ValueState FileState FileState
Lens' ValueState FileState
lensVStoFS ASetter ValueState ValueState FileState FileState
-> (([String] -> Identity [String])
-> FileState -> Identity FileState)
-> ASetter ValueState ValueState [String] [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([String] -> Identity [String]) -> FileState -> Identity FileState
Lens' FileState [String]
using) (\[String]
us -> [String] -> [String]
forall a. Ord a => [a] -> [a]
nubSort ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String
uString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
us)
getUsing :: FS [String]
getUsing :: FS [String]
getUsing = (FileState -> [String]) -> FS [String]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (FileState -> Getting [String] FileState [String] -> [String]
forall s a. s -> Getting a s a -> a
^. Getting [String] FileState [String]
Lens' FileState [String]
using)
addHeaderUsing :: String -> ValueState -> ValueState
String
u = ASetter ValueState ValueState [String] [String]
-> ([String] -> [String]) -> ValueState -> ValueState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (ASetter ValueState ValueState FileState FileState
Lens' ValueState FileState
lensVStoFS ASetter ValueState ValueState FileState FileState
-> (([String] -> Identity [String])
-> FileState -> Identity FileState)
-> ASetter ValueState ValueState [String] [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([String] -> Identity [String]) -> FileState -> Identity FileState
Lens' FileState [String]
headerUsing) (\[String]
us -> [String] -> [String]
forall a. Ord a => [a] -> [a]
nubSort ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String
uString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
us)
getHeaderUsing :: FS [String]
= (FileState -> [String]) -> FS [String]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (FileState -> Getting [String] FileState [String] -> [String]
forall s a. s -> Getting a s a -> a
^. Getting [String] FileState [String]
Lens' FileState [String]
headerUsing)
setMainDoc :: Doc -> MethodState -> MethodState
setMainDoc :: Doc -> MethodState -> MethodState
setMainDoc Doc
d = ASetter MethodState MethodState FileState FileState
-> (FileState -> FileState) -> MethodState -> MethodState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter MethodState MethodState FileState FileState
Lens' MethodState FileState
lensMStoFS ((FileState -> FileState) -> MethodState -> MethodState)
-> (FileState -> FileState) -> MethodState -> MethodState
forall a b. (a -> b) -> a -> b
$ ASetter FileState FileState Doc Doc
-> Doc -> FileState -> FileState
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter FileState FileState Doc Doc
Lens' FileState Doc
mainDoc Doc
d
getMainDoc :: FS Doc
getMainDoc :: FS Doc
getMainDoc = (FileState -> Doc) -> FS Doc
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (FileState -> Getting Doc FileState Doc -> Doc
forall s a. s -> Getting a s a -> a
^. Getting Doc FileState Doc
Lens' FileState Doc
mainDoc)
setFileType :: FileType -> FileState -> FileState
setFileType :: FileType -> FileState -> FileState
setFileType = ASetter FileState FileState FileType FileType
-> FileType -> FileState -> FileState
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter FileState FileState FileType FileType
Lens' FileState FileType
currFileType
setModuleName :: String -> FileState -> FileState
setModuleName :: String -> FileState -> FileState
setModuleName = ASetter FileState FileState String String
-> String -> FileState -> FileState
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter FileState FileState String String
Lens' FileState String
currModName
getModuleName :: FS String
getModuleName :: FS String
getModuleName = (FileState -> String) -> FS String
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (FileState -> Getting String FileState String -> String
forall s a. s -> Getting a s a -> a
^. Getting String FileState String
Lens' FileState String
currModName)
setClassName :: String -> ClassState -> ClassState
setClassName :: String -> ClassState -> ClassState
setClassName = ASetter ClassState ClassState String String
-> String -> ClassState -> ClassState
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter ClassState ClassState String String
Lens' ClassState String
currClassName
getClassName :: MS ClassName
getClassName :: MS String
getClassName = (MethodState -> String) -> MS String
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (MethodState -> Getting String MethodState String -> String
forall s a. s -> Getting a s a -> a
^. ((ClassState -> Const String ClassState)
-> MethodState -> Const String MethodState
Lens' MethodState ClassState
classState ((ClassState -> Const String ClassState)
-> MethodState -> Const String MethodState)
-> ((String -> Const String String)
-> ClassState -> Const String ClassState)
-> Getting String MethodState String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Const String String)
-> ClassState -> Const String ClassState
Lens' ClassState String
currClassName))
setCurrMain :: MethodState -> MethodState
setCurrMain :: MethodState -> MethodState
setCurrMain = ASetter MethodState MethodState Bool Bool
-> (Bool -> Bool) -> MethodState -> MethodState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (ASetter MethodState MethodState FileState FileState
Lens' MethodState FileState
lensMStoFS ASetter MethodState MethodState FileState FileState
-> ((Bool -> Identity Bool) -> FileState -> Identity FileState)
-> ASetter MethodState MethodState Bool Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Identity Bool) -> FileState -> Identity FileState
Lens' FileState Bool
currMain) (\Bool
b -> if Bool
b then
String -> Bool
forall a. HasCallStack => String -> a
error String
"Multiple main functions defined" else Bool -> Bool
not Bool
b)
getCurrMain :: FS Bool
getCurrMain :: FS Bool
getCurrMain = (FileState -> Bool) -> FS Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (FileState -> Getting Bool FileState Bool -> Bool
forall s a. s -> Getting a s a -> a
^. Getting Bool FileState Bool
Lens' FileState Bool
currMain)
addClass :: String -> ClassState -> ClassState
addClass :: String -> ClassState -> ClassState
addClass String
c = ASetter ClassState ClassState [String] [String]
-> ([String] -> [String]) -> ClassState -> ClassState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (ASetter ClassState ClassState FileState FileState
Lens' ClassState FileState
fileState ASetter ClassState ClassState FileState FileState
-> (([String] -> Identity [String])
-> FileState -> Identity FileState)
-> ASetter ClassState ClassState [String] [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([String] -> Identity [String]) -> FileState -> Identity FileState
Lens' FileState [String]
currClasses) (\[String]
cs -> String -> [String] -> String -> [String]
forall a. Eq a => a -> [a] -> String -> [a]
ifElemError String
c [String]
cs
String
"Multiple classes with same name in same file")
getClasses :: FS [String]
getClasses :: FS [String]
getClasses = (FileState -> [String]) -> FS [String]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (FileState -> Getting [String] FileState [String] -> [String]
forall s a. s -> Getting a s a -> a
^. Getting [String] FileState [String]
Lens' FileState [String]
currClasses)
updateClassMap :: String -> FileState -> FileState
updateClassMap :: String -> FileState -> FileState
updateClassMap String
n FileState
fs = ASetter FileState FileState (Map String String) (Map String String)
-> (Map String String -> Map String String)
-> FileState
-> FileState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (ASetter FileState FileState GOOLState GOOLState
Lens' FileState GOOLState
goolState ASetter FileState FileState GOOLState GOOLState
-> ((Map String String -> Identity (Map String String))
-> GOOLState -> Identity GOOLState)
-> ASetter
FileState FileState (Map String String) (Map String String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Map String String -> Identity (Map String String))
-> GOOLState -> Identity GOOLState
Lens' GOOLState (Map String String)
classMap) (Map String String -> Map String String -> Map String String
forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union ([(String, String)] -> Map String String
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(String, String)] -> Map String String)
-> [(String, String)] -> Map String String
forall a b. (a -> b) -> a -> b
$
(String -> (String, String)) -> [String] -> [(String, String)]
forall a b. (a -> b) -> [a] -> [b]
map (String
n,) (FileState
fs FileState -> Getting [String] FileState [String] -> [String]
forall s a. s -> Getting a s a -> a
^. Getting [String] FileState [String]
Lens' FileState [String]
currClasses))) FileState
fs
getClassMap :: VS (Map String String)
getClassMap :: VS (Map String String)
getClassMap = (ValueState -> Map String String) -> VS (Map String String)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (ValueState
-> Getting (Map String String) ValueState (Map String String)
-> Map String String
forall s a. s -> Getting a s a -> a
^. ((FileState -> Const (Map String String) FileState)
-> ValueState -> Const (Map String String) ValueState
Lens' ValueState FileState
lensVStoFS ((FileState -> Const (Map String String) FileState)
-> ValueState -> Const (Map String String) ValueState)
-> ((Map String String
-> Const (Map String String) (Map String String))
-> FileState -> Const (Map String String) FileState)
-> Getting (Map String String) ValueState (Map String String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GOOLState -> Const (Map String String) GOOLState)
-> FileState -> Const (Map String String) FileState
Lens' FileState GOOLState
goolState ((GOOLState -> Const (Map String String) GOOLState)
-> FileState -> Const (Map String String) FileState)
-> ((Map String String
-> Const (Map String String) (Map String String))
-> GOOLState -> Const (Map String String) GOOLState)
-> (Map String String
-> Const (Map String String) (Map String String))
-> FileState
-> Const (Map String String) FileState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Map String String
-> Const (Map String String) (Map String String))
-> GOOLState -> Const (Map String String) GOOLState
Lens' GOOLState (Map String String)
classMap))
updateMethodExcMap :: String -> MethodState -> MethodState
updateMethodExcMap :: String -> MethodState -> MethodState
updateMethodExcMap String
n MethodState
ms = ASetter
MethodState
MethodState
(Map QualifiedName [ExceptionType])
(Map QualifiedName [ExceptionType])
-> (Map QualifiedName [ExceptionType]
-> Map QualifiedName [ExceptionType])
-> MethodState
-> MethodState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (ASetter MethodState MethodState FileState FileState
Lens' MethodState FileState
lensMStoFS ASetter MethodState MethodState FileState FileState
-> ((Map QualifiedName [ExceptionType]
-> Identity (Map QualifiedName [ExceptionType]))
-> FileState -> Identity FileState)
-> ASetter
MethodState
MethodState
(Map QualifiedName [ExceptionType])
(Map QualifiedName [ExceptionType])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASetter FileState FileState GOOLState GOOLState
Lens' FileState GOOLState
goolState ASetter FileState FileState GOOLState GOOLState
-> ((Map QualifiedName [ExceptionType]
-> Identity (Map QualifiedName [ExceptionType]))
-> GOOLState -> Identity GOOLState)
-> (Map QualifiedName [ExceptionType]
-> Identity (Map QualifiedName [ExceptionType]))
-> FileState
-> Identity FileState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Map QualifiedName [ExceptionType]
-> Identity (Map QualifiedName [ExceptionType]))
-> GOOLState -> Identity GOOLState
Lens' GOOLState (Map QualifiedName [ExceptionType])
methodExceptionMap)
(QualifiedName
-> [ExceptionType]
-> Map QualifiedName [ExceptionType]
-> Map QualifiedName [ExceptionType]
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (String -> String -> QualifiedName
qualName String
mn String
n) (MethodState
ms MethodState
-> Getting [ExceptionType] MethodState [ExceptionType]
-> [ExceptionType]
forall s a. s -> Getting a s a -> a
^. Getting [ExceptionType] MethodState [ExceptionType]
Lens' MethodState [ExceptionType]
exceptions)) MethodState
ms
where mn :: String
mn = MethodState
ms MethodState -> Getting String MethodState String -> String
forall s a. s -> Getting a s a -> a
^. ((FileState -> Const String FileState)
-> MethodState -> Const String MethodState
Lens' MethodState FileState
lensMStoFS ((FileState -> Const String FileState)
-> MethodState -> Const String MethodState)
-> Getting String FileState String
-> Getting String MethodState String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting String FileState String
Lens' FileState String
currModName)
getMethodExcMap :: VS (Map QualifiedName [ExceptionType])
getMethodExcMap :: VS (Map QualifiedName [ExceptionType])
getMethodExcMap = (ValueState -> Map QualifiedName [ExceptionType])
-> VS (Map QualifiedName [ExceptionType])
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (ValueState
-> Getting
(Map QualifiedName [ExceptionType])
ValueState
(Map QualifiedName [ExceptionType])
-> Map QualifiedName [ExceptionType]
forall s a. s -> Getting a s a -> a
^. ((FileState -> Const (Map QualifiedName [ExceptionType]) FileState)
-> ValueState
-> Const (Map QualifiedName [ExceptionType]) ValueState
Lens' ValueState FileState
lensVStoFS ((FileState -> Const (Map QualifiedName [ExceptionType]) FileState)
-> ValueState
-> Const (Map QualifiedName [ExceptionType]) ValueState)
-> ((Map QualifiedName [ExceptionType]
-> Const
(Map QualifiedName [ExceptionType])
(Map QualifiedName [ExceptionType]))
-> FileState
-> Const (Map QualifiedName [ExceptionType]) FileState)
-> Getting
(Map QualifiedName [ExceptionType])
ValueState
(Map QualifiedName [ExceptionType])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GOOLState -> Const (Map QualifiedName [ExceptionType]) GOOLState)
-> FileState -> Const (Map QualifiedName [ExceptionType]) FileState
Lens' FileState GOOLState
goolState ((GOOLState -> Const (Map QualifiedName [ExceptionType]) GOOLState)
-> FileState
-> Const (Map QualifiedName [ExceptionType]) FileState)
-> ((Map QualifiedName [ExceptionType]
-> Const
(Map QualifiedName [ExceptionType])
(Map QualifiedName [ExceptionType]))
-> GOOLState
-> Const (Map QualifiedName [ExceptionType]) GOOLState)
-> (Map QualifiedName [ExceptionType]
-> Const
(Map QualifiedName [ExceptionType])
(Map QualifiedName [ExceptionType]))
-> FileState
-> Const (Map QualifiedName [ExceptionType]) FileState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Map QualifiedName [ExceptionType]
-> Const
(Map QualifiedName [ExceptionType])
(Map QualifiedName [ExceptionType]))
-> GOOLState -> Const (Map QualifiedName [ExceptionType]) GOOLState
Lens' GOOLState (Map QualifiedName [ExceptionType])
methodExceptionMap))
updateCallMap :: String -> MethodState -> MethodState
updateCallMap :: String -> MethodState -> MethodState
updateCallMap String
n MethodState
ms = ASetter
MethodState
MethodState
(Map QualifiedName [QualifiedName])
(Map QualifiedName [QualifiedName])
-> (Map QualifiedName [QualifiedName]
-> Map QualifiedName [QualifiedName])
-> MethodState
-> MethodState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (ASetter MethodState MethodState FileState FileState
Lens' MethodState FileState
lensMStoFS ASetter MethodState MethodState FileState FileState
-> ((Map QualifiedName [QualifiedName]
-> Identity (Map QualifiedName [QualifiedName]))
-> FileState -> Identity FileState)
-> ASetter
MethodState
MethodState
(Map QualifiedName [QualifiedName])
(Map QualifiedName [QualifiedName])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASetter FileState FileState GOOLState GOOLState
Lens' FileState GOOLState
goolState ASetter FileState FileState GOOLState GOOLState
-> ((Map QualifiedName [QualifiedName]
-> Identity (Map QualifiedName [QualifiedName]))
-> GOOLState -> Identity GOOLState)
-> (Map QualifiedName [QualifiedName]
-> Identity (Map QualifiedName [QualifiedName]))
-> FileState
-> Identity FileState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Map QualifiedName [QualifiedName]
-> Identity (Map QualifiedName [QualifiedName]))
-> GOOLState -> Identity GOOLState
Lens' GOOLState (Map QualifiedName [QualifiedName])
callMap)
(QualifiedName
-> [QualifiedName]
-> Map QualifiedName [QualifiedName]
-> Map QualifiedName [QualifiedName]
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (String -> String -> QualifiedName
qualName String
mn String
n) (MethodState
ms MethodState
-> Getting [QualifiedName] MethodState [QualifiedName]
-> [QualifiedName]
forall s a. s -> Getting a s a -> a
^. Getting [QualifiedName] MethodState [QualifiedName]
Lens' MethodState [QualifiedName]
calls)) MethodState
ms
where mn :: String
mn = MethodState
ms MethodState -> Getting String MethodState String -> String
forall s a. s -> Getting a s a -> a
^. ((FileState -> Const String FileState)
-> MethodState -> Const String MethodState
Lens' MethodState FileState
lensMStoFS ((FileState -> Const String FileState)
-> MethodState -> Const String MethodState)
-> Getting String FileState String
-> Getting String MethodState String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting String FileState String
Lens' FileState String
currModName)
callMapTransClosure :: GOOLState -> GOOLState
callMapTransClosure :: GOOLState -> GOOLState
callMapTransClosure = ((Map QualifiedName [QualifiedName]
-> Identity (Map QualifiedName [QualifiedName]))
-> GOOLState -> Identity GOOLState)
-> (Map QualifiedName [QualifiedName]
-> Map QualifiedName [QualifiedName])
-> GOOLState
-> GOOLState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (Map QualifiedName [QualifiedName]
-> Identity (Map QualifiedName [QualifiedName]))
-> GOOLState -> Identity GOOLState
Lens' GOOLState (Map QualifiedName [QualifiedName])
callMap Map QualifiedName [QualifiedName]
-> Map QualifiedName [QualifiedName]
tClosure
where tClosure :: Map QualifiedName [QualifiedName]
-> Map QualifiedName [QualifiedName]
tClosure Map QualifiedName [QualifiedName]
m = ([QualifiedName] -> [QualifiedName])
-> Map QualifiedName [QualifiedName]
-> Map QualifiedName [QualifiedName]
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map (Map QualifiedName [QualifiedName]
-> [QualifiedName] -> [QualifiedName]
traceCalls Map QualifiedName [QualifiedName]
m) Map QualifiedName [QualifiedName]
m
traceCalls :: Map QualifiedName [QualifiedName] -> [QualifiedName] ->
[QualifiedName]
traceCalls :: Map QualifiedName [QualifiedName]
-> [QualifiedName] -> [QualifiedName]
traceCalls Map QualifiedName [QualifiedName]
_ [] = []
traceCalls Map QualifiedName [QualifiedName]
cm (QualifiedName
c:[QualifiedName]
cs) = QualifiedName
c QualifiedName -> [QualifiedName] -> [QualifiedName]
forall a. a -> [a] -> [a]
: Map QualifiedName [QualifiedName]
-> [QualifiedName] -> [QualifiedName]
traceCalls Map QualifiedName [QualifiedName]
cm ([QualifiedName]
cs [QualifiedName] -> [QualifiedName] -> [QualifiedName]
forall a. [a] -> [a] -> [a]
++
[QualifiedName]
-> QualifiedName
-> Map QualifiedName [QualifiedName]
-> [QualifiedName]
forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault [] QualifiedName
c Map QualifiedName [QualifiedName]
cm)
updateMEMWithCalls :: GOOLState -> GOOLState
updateMEMWithCalls :: GOOLState -> GOOLState
updateMEMWithCalls GOOLState
s = ((Map QualifiedName [ExceptionType]
-> Identity (Map QualifiedName [ExceptionType]))
-> GOOLState -> Identity GOOLState)
-> (Map QualifiedName [ExceptionType]
-> Map QualifiedName [ExceptionType])
-> GOOLState
-> GOOLState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (Map QualifiedName [ExceptionType]
-> Identity (Map QualifiedName [ExceptionType]))
-> GOOLState -> Identity GOOLState
Lens' GOOLState (Map QualifiedName [ExceptionType])
methodExceptionMap (\Map QualifiedName [ExceptionType]
mem -> (QualifiedName -> [ExceptionType] -> [ExceptionType])
-> Map QualifiedName [ExceptionType]
-> Map QualifiedName [ExceptionType]
forall k a b. (k -> a -> b) -> Map k a -> Map k b
Map.mapWithKey
(Map QualifiedName [ExceptionType]
-> Map QualifiedName [QualifiedName]
-> QualifiedName
-> [ExceptionType]
-> [ExceptionType]
addCallExcs Map QualifiedName [ExceptionType]
mem (GOOLState
s GOOLState
-> Getting
(Map QualifiedName [QualifiedName])
GOOLState
(Map QualifiedName [QualifiedName])
-> Map QualifiedName [QualifiedName]
forall s a. s -> Getting a s a -> a
^. Getting
(Map QualifiedName [QualifiedName])
GOOLState
(Map QualifiedName [QualifiedName])
Lens' GOOLState (Map QualifiedName [QualifiedName])
callMap)) Map QualifiedName [ExceptionType]
mem) GOOLState
s
where addCallExcs :: Map QualifiedName [ExceptionType] ->
Map QualifiedName [QualifiedName] -> QualifiedName -> [ExceptionType]
-> [ExceptionType]
addCallExcs :: Map QualifiedName [ExceptionType]
-> Map QualifiedName [QualifiedName]
-> QualifiedName
-> [ExceptionType]
-> [ExceptionType]
addCallExcs Map QualifiedName [ExceptionType]
mem Map QualifiedName [QualifiedName]
cm QualifiedName
f [ExceptionType]
es = [ExceptionType] -> [ExceptionType]
forall a. Eq a => [a] -> [a]
nub ([ExceptionType] -> [ExceptionType])
-> [ExceptionType] -> [ExceptionType]
forall a b. (a -> b) -> a -> b
$ [ExceptionType]
es [ExceptionType] -> [ExceptionType] -> [ExceptionType]
forall a. [a] -> [a] -> [a]
++ (QualifiedName -> [ExceptionType])
-> [QualifiedName] -> [ExceptionType]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\QualifiedName
fn -> [ExceptionType]
-> QualifiedName
-> Map QualifiedName [ExceptionType]
-> [ExceptionType]
forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault
[] QualifiedName
fn Map QualifiedName [ExceptionType]
mem) ([QualifiedName]
-> QualifiedName
-> Map QualifiedName [QualifiedName]
-> [QualifiedName]
forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault [] QualifiedName
f Map QualifiedName [QualifiedName]
cm)
addParameter :: String -> MethodState -> MethodState
addParameter :: String -> MethodState -> MethodState
addParameter String
p = ASetter MethodState MethodState [String] [String]
-> ([String] -> [String]) -> MethodState -> MethodState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter MethodState MethodState [String] [String]
Lens' MethodState [String]
currParameters (\[String]
ps -> String -> [String] -> String -> [String]
forall a. Eq a => a -> [a] -> String -> [a]
ifElemError String
p [String]
ps (String -> [String]) -> String -> [String]
forall a b. (a -> b) -> a -> b
$
String
"Function has duplicate parameter: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
p)
getParameters :: MS [String]
getParameters :: MS [String]
getParameters = (MethodState -> [String]) -> MS [String]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets ([String] -> [String]
forall a. [a] -> [a]
reverse ([String] -> [String])
-> (MethodState -> [String]) -> MethodState -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (MethodState -> Getting [String] MethodState [String] -> [String]
forall s a. s -> Getting a s a -> a
^. Getting [String] MethodState [String]
Lens' MethodState [String]
currParameters))
setOutputsDeclared :: MethodState -> MethodState
setOutputsDeclared :: MethodState -> MethodState
setOutputsDeclared = ASetter MethodState MethodState Bool Bool
-> Bool -> MethodState -> MethodState
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter MethodState MethodState Bool Bool
Lens' MethodState Bool
outputsDeclared Bool
True
isOutputsDeclared :: MS Bool
isOutputsDeclared :: MS Bool
isOutputsDeclared = (MethodState -> Bool) -> MS Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (MethodState -> Getting Bool MethodState Bool -> Bool
forall s a. s -> Getting a s a -> a
^. Getting Bool MethodState Bool
Lens' MethodState Bool
outputsDeclared)
addException :: ExceptionType -> MethodState -> MethodState
addException :: ExceptionType -> MethodState -> MethodState
addException ExceptionType
e = ASetter MethodState MethodState [ExceptionType] [ExceptionType]
-> ([ExceptionType] -> [ExceptionType])
-> MethodState
-> MethodState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter MethodState MethodState [ExceptionType] [ExceptionType]
Lens' MethodState [ExceptionType]
exceptions (\[ExceptionType]
es -> [ExceptionType] -> [ExceptionType]
forall a. Eq a => [a] -> [a]
nub ([ExceptionType] -> [ExceptionType])
-> [ExceptionType] -> [ExceptionType]
forall a b. (a -> b) -> a -> b
$ ExceptionType
e ExceptionType -> [ExceptionType] -> [ExceptionType]
forall a. a -> [a] -> [a]
: [ExceptionType]
es)
addExceptions :: [ExceptionType] -> ValueState -> ValueState
addExceptions :: [ExceptionType] -> ValueState -> ValueState
addExceptions [ExceptionType]
es = ASetter ValueState ValueState [ExceptionType] [ExceptionType]
-> ([ExceptionType] -> [ExceptionType]) -> ValueState -> ValueState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ((MethodState -> Identity MethodState)
-> ValueState -> Identity ValueState
Iso' ValueState MethodState
methodState ((MethodState -> Identity MethodState)
-> ValueState -> Identity ValueState)
-> ASetter MethodState MethodState [ExceptionType] [ExceptionType]
-> ASetter ValueState ValueState [ExceptionType] [ExceptionType]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASetter MethodState MethodState [ExceptionType] [ExceptionType]
Lens' MethodState [ExceptionType]
exceptions) (\[ExceptionType]
exs -> [ExceptionType] -> [ExceptionType]
forall a. Eq a => [a] -> [a]
nub ([ExceptionType] -> [ExceptionType])
-> [ExceptionType] -> [ExceptionType]
forall a b. (a -> b) -> a -> b
$ [ExceptionType]
es [ExceptionType] -> [ExceptionType] -> [ExceptionType]
forall a. [a] -> [a] -> [a]
++ [ExceptionType]
exs)
getExceptions :: MS [ExceptionType]
getExceptions :: MS [ExceptionType]
getExceptions = (MethodState -> [ExceptionType]) -> MS [ExceptionType]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (MethodState
-> Getting [ExceptionType] MethodState [ExceptionType]
-> [ExceptionType]
forall s a. s -> Getting a s a -> a
^. Getting [ExceptionType] MethodState [ExceptionType]
Lens' MethodState [ExceptionType]
exceptions)
addCall :: QualifiedName -> ValueState -> ValueState
addCall :: QualifiedName -> ValueState -> ValueState
addCall QualifiedName
f = ASetter ValueState ValueState [QualifiedName] [QualifiedName]
-> ([QualifiedName] -> [QualifiedName]) -> ValueState -> ValueState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ((MethodState -> Identity MethodState)
-> ValueState -> Identity ValueState
Iso' ValueState MethodState
methodState ((MethodState -> Identity MethodState)
-> ValueState -> Identity ValueState)
-> (([QualifiedName] -> Identity [QualifiedName])
-> MethodState -> Identity MethodState)
-> ASetter ValueState ValueState [QualifiedName] [QualifiedName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([QualifiedName] -> Identity [QualifiedName])
-> MethodState -> Identity MethodState
Lens' MethodState [QualifiedName]
calls) (QualifiedName
fQualifiedName -> [QualifiedName] -> [QualifiedName]
forall a. a -> [a] -> [a]
:)
setVisibility :: VisibilityTag -> MethodState -> MethodState
setVisibility :: VisibilityTag -> MethodState -> MethodState
setVisibility = ASetter MethodState MethodState VisibilityTag VisibilityTag
-> VisibilityTag -> MethodState -> MethodState
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter MethodState MethodState VisibilityTag VisibilityTag
Lens' MethodState VisibilityTag
currVisibility
getVisibility :: MS VisibilityTag
getVisibility :: MS VisibilityTag
getVisibility = (MethodState -> VisibilityTag) -> MS VisibilityTag
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (MethodState
-> Getting VisibilityTag MethodState VisibilityTag -> VisibilityTag
forall s a. s -> Getting a s a -> a
^. Getting VisibilityTag MethodState VisibilityTag
Lens' MethodState VisibilityTag
currVisibility)
setCurrMainFunc :: Bool -> MethodState -> MethodState
setCurrMainFunc :: Bool -> MethodState -> MethodState
setCurrMainFunc = ASetter MethodState MethodState Bool Bool
-> Bool -> MethodState -> MethodState
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter MethodState MethodState Bool Bool
Lens' MethodState Bool
currMainFunc
getCurrMainFunc :: MS Bool
getCurrMainFunc :: MS Bool
getCurrMainFunc = (MethodState -> Bool) -> MS Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (MethodState -> Getting Bool MethodState Bool -> Bool
forall s a. s -> Getting a s a -> a
^. Getting Bool MethodState Bool
Lens' MethodState Bool
currMainFunc)
setThrowUsed :: MethodState -> MethodState
setThrowUsed :: MethodState -> MethodState
setThrowUsed = ASetter MethodState MethodState Bool Bool
-> Bool -> MethodState -> MethodState
forall s t a b. ASetter s t a b -> b -> s -> t
set ((GOOLState -> Identity GOOLState)
-> MethodState -> Identity MethodState
Lens' MethodState GOOLState
lensMStoGS ((GOOLState -> Identity GOOLState)
-> MethodState -> Identity MethodState)
-> ((Bool -> Identity Bool) -> GOOLState -> Identity GOOLState)
-> ASetter MethodState MethodState Bool Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Identity Bool) -> GOOLState -> Identity GOOLState
Lens' GOOLState Bool
throwUsed) Bool
True
getThrowUsed :: MS Bool
getThrowUsed :: MS Bool
getThrowUsed = (MethodState -> Bool) -> MS Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (MethodState -> Getting Bool MethodState Bool -> Bool
forall s a. s -> Getting a s a -> a
^. ((GOOLState -> Const Bool GOOLState)
-> MethodState -> Const Bool MethodState
Lens' MethodState GOOLState
lensMStoGS ((GOOLState -> Const Bool GOOLState)
-> MethodState -> Const Bool MethodState)
-> ((Bool -> Const Bool Bool) -> GOOLState -> Const Bool GOOLState)
-> Getting Bool MethodState Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Const Bool Bool) -> GOOLState -> Const Bool GOOLState
Lens' GOOLState Bool
throwUsed))
setErrorDefined :: MethodState -> MethodState
setErrorDefined :: MethodState -> MethodState
setErrorDefined = ASetter MethodState MethodState Bool Bool
-> Bool -> MethodState -> MethodState
forall s t a b. ASetter s t a b -> b -> s -> t
set ((GOOLState -> Identity GOOLState)
-> MethodState -> Identity MethodState
Lens' MethodState GOOLState
lensMStoGS ((GOOLState -> Identity GOOLState)
-> MethodState -> Identity MethodState)
-> ((Bool -> Identity Bool) -> GOOLState -> Identity GOOLState)
-> ASetter MethodState MethodState Bool Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Identity Bool) -> GOOLState -> Identity GOOLState
Lens' GOOLState Bool
errorDefined) Bool
True
getErrorDefined :: MS Bool
getErrorDefined :: MS Bool
getErrorDefined = (MethodState -> Bool) -> MS Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (MethodState -> Getting Bool MethodState Bool -> Bool
forall s a. s -> Getting a s a -> a
^. ((GOOLState -> Const Bool GOOLState)
-> MethodState -> Const Bool MethodState
Lens' MethodState GOOLState
lensMStoGS ((GOOLState -> Const Bool GOOLState)
-> MethodState -> Const Bool MethodState)
-> ((Bool -> Const Bool Bool) -> GOOLState -> Const Bool GOOLState)
-> Getting Bool MethodState Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Const Bool Bool) -> GOOLState -> Const Bool GOOLState
Lens' GOOLState Bool
errorDefined))
incrementLine :: MethodState -> MethodState
incrementLine :: MethodState -> MethodState
incrementLine = ASetter MethodState MethodState Index Index
-> (Index -> Index) -> MethodState -> MethodState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (((Index, Index) -> Identity (Index, Index))
-> MethodState -> Identity MethodState
Lens' MethodState (Index, Index)
contentsIndices (((Index, Index) -> Identity (Index, Index))
-> MethodState -> Identity MethodState)
-> ((Index -> Identity Index)
-> (Index, Index) -> Identity (Index, Index))
-> ASetter MethodState MethodState Index Index
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Index -> Identity Index)
-> (Index, Index) -> Identity (Index, Index)
forall s t a b. Field1 s t a b => Lens s t a b
Lens (Index, Index) (Index, Index) Index Index
_1) (Index -> Index -> Index
forall a. Num a => a -> a -> a
+Index
1) (MethodState -> MethodState)
-> (MethodState -> MethodState) -> MethodState -> MethodState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASetter MethodState MethodState Index Index
-> Index -> MethodState -> MethodState
forall s t a b. ASetter s t a b -> b -> s -> t
set (((Index, Index) -> Identity (Index, Index))
-> MethodState -> Identity MethodState
Lens' MethodState (Index, Index)
contentsIndices (((Index, Index) -> Identity (Index, Index))
-> MethodState -> Identity MethodState)
-> ((Index -> Identity Index)
-> (Index, Index) -> Identity (Index, Index))
-> ASetter MethodState MethodState Index Index
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Index -> Identity Index)
-> (Index, Index) -> Identity (Index, Index)
forall s t a b. Field2 s t a b => Lens s t a b
Lens (Index, Index) (Index, Index) Index Index
_2) Index
0
incrementWord :: MethodState -> MethodState
incrementWord :: MethodState -> MethodState
incrementWord = ASetter MethodState MethodState Index Index
-> (Index -> Index) -> MethodState -> MethodState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (((Index, Index) -> Identity (Index, Index))
-> MethodState -> Identity MethodState
Lens' MethodState (Index, Index)
contentsIndices (((Index, Index) -> Identity (Index, Index))
-> MethodState -> Identity MethodState)
-> ((Index -> Identity Index)
-> (Index, Index) -> Identity (Index, Index))
-> ASetter MethodState MethodState Index Index
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Index -> Identity Index)
-> (Index, Index) -> Identity (Index, Index)
forall s t a b. Field2 s t a b => Lens s t a b
Lens (Index, Index) (Index, Index) Index Index
_2) (Index -> Index -> Index
forall a. Num a => a -> a -> a
+Index
1)
getLineIndex :: MS Index
getLineIndex :: MS Index
getLineIndex = (MethodState -> Index) -> MS Index
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (MethodState -> Getting Index MethodState Index -> Index
forall s a. s -> Getting a s a -> a
^. (((Index, Index) -> Const Index (Index, Index))
-> MethodState -> Const Index MethodState
Lens' MethodState (Index, Index)
contentsIndices (((Index, Index) -> Const Index (Index, Index))
-> MethodState -> Const Index MethodState)
-> ((Index -> Const Index Index)
-> (Index, Index) -> Const Index (Index, Index))
-> Getting Index MethodState Index
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Index -> Const Index Index)
-> (Index, Index) -> Const Index (Index, Index)
forall s t a b. Field1 s t a b => Lens s t a b
Lens (Index, Index) (Index, Index) Index Index
_1))
getWordIndex :: MS Index
getWordIndex :: MS Index
getWordIndex = (MethodState -> Index) -> MS Index
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (MethodState -> Getting Index MethodState Index -> Index
forall s a. s -> Getting a s a -> a
^. (((Index, Index) -> Const Index (Index, Index))
-> MethodState -> Const Index MethodState
Lens' MethodState (Index, Index)
contentsIndices (((Index, Index) -> Const Index (Index, Index))
-> MethodState -> Const Index MethodState)
-> ((Index -> Const Index Index)
-> (Index, Index) -> Const Index (Index, Index))
-> Getting Index MethodState Index
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Index -> Const Index Index)
-> (Index, Index) -> Const Index (Index, Index)
forall s t a b. Field2 s t a b => Lens s t a b
Lens (Index, Index) (Index, Index) Index Index
_2))
resetIndices :: MethodState -> MethodState
resetIndices :: MethodState -> MethodState
resetIndices = (((Index, Index) -> Identity (Index, Index))
-> MethodState -> Identity MethodState)
-> (Index, Index) -> MethodState -> MethodState
forall s t a b. ASetter s t a b -> b -> s -> t
set ((Index, Index) -> Identity (Index, Index))
-> MethodState -> Identity MethodState
Lens' MethodState (Index, Index)
contentsIndices (Index
0,Index
0)
useVarName :: String -> MethodState -> MethodState
useVarName :: String -> MethodState -> MethodState
useVarName String
v = ASetter MethodState MethodState (Maybe Int) (Maybe Int)
-> (Maybe Int -> Maybe Int) -> MethodState -> MethodState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ((Map String Int -> Identity (Map String Int))
-> MethodState -> Identity MethodState
Lens' MethodState (Map String Int)
varNames ((Map String Int -> Identity (Map String Int))
-> MethodState -> Identity MethodState)
-> ((Maybe Int -> Identity (Maybe Int))
-> Map String Int -> Identity (Map String Int))
-> ASetter MethodState MethodState (Maybe Int) (Maybe Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (Map String Int)
-> Lens' (Map String Int) (Maybe (IxValue (Map String Int)))
forall m. At m => Index m -> Lens' m (Maybe (IxValue m))
at String
Index (Map String Int)
prefix) (Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> (Maybe Int -> Int) -> Maybe Int -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
nextSuffix (Int -> Int) -> (Maybe Int -> Int) -> Maybe Int -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
0)
where (String
prefix, Int
nextSuffix) = ASetter (String, Maybe Int) (String, Int) (Maybe Int) Int
-> (Maybe Int -> Int) -> (String, Maybe Int) -> (String, Int)
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter (String, Maybe Int) (String, Int) (Maybe Int) Int
forall s t a b. Field2 s t a b => Lens s t a b
Lens (String, Maybe Int) (String, Int) (Maybe Int) Int
_2 (Int -> (Int -> Int) -> Maybe Int -> Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int
0 (Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)) ((String, Maybe Int) -> (String, Int))
-> (String, Maybe Int) -> (String, Int)
forall a b. (a -> b) -> a -> b
$ String -> (String, Maybe Int)
splitVarName String
v
genVarName :: [String] -> String -> MS String
genVarName :: [String] -> String -> MS String
genVarName [String]
candidates String
backup = do
Map String Int
used <- (MethodState -> Map String Int)
-> StateT MethodState Identity (Map String Int)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (MethodState
-> Getting (Map String Int) MethodState (Map String Int)
-> Map String Int
forall s a. s -> Getting a s a -> a
^. Getting (Map String Int) MethodState (Map String Int)
Lens' MethodState (Map String Int)
varNames)
let
isAvailable :: (String, Maybe Int) -> Bool
isAvailable (String
n,Maybe Int
c) = Bool -> (Int -> Bool) -> Maybe Int -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
True ((Int -> Bool) -> (Int -> Int -> Bool) -> Maybe Int -> Int -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Bool -> Int -> Bool
forall a b. a -> b -> a
const Bool
False) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
(>=) Maybe Int
c) (Maybe Int -> Bool) -> Maybe Int -> Bool
forall a b. (a -> b) -> a -> b
$ String -> Map String Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup String
n Map String Int
used
choice :: (String, Maybe Int)
choice = ((String, Maybe Int) -> (String, Maybe Int) -> (String, Maybe Int))
-> (String, Maybe Int)
-> [(String, Maybe Int)]
-> (String, Maybe Int)
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (String, Maybe Int) -> (String, Maybe Int) -> (String, Maybe Int)
forall a b. a -> b -> a
const (String -> (String, Maybe Int)
splitVarName String
backup) ([(String, Maybe Int)] -> (String, Maybe Int))
-> [(String, Maybe Int)] -> (String, Maybe Int)
forall a b. (a -> b) -> a -> b
$ ((String, Maybe Int) -> Bool)
-> [(String, Maybe Int)] -> [(String, Maybe Int)]
forall a. (a -> Bool) -> [a] -> [a]
filter (String, Maybe Int) -> Bool
isAvailable ([(String, Maybe Int)] -> [(String, Maybe Int)])
-> [(String, Maybe Int)] -> [(String, Maybe Int)]
forall a b. (a -> b) -> a -> b
$ (String -> (String, Maybe Int))
-> [String] -> [(String, Maybe Int)]
forall a b. (a -> b) -> [a] -> [b]
map String -> (String, Maybe Int)
splitVarName [String]
candidates
(String, Maybe Int) -> MS String
bumpVarName (String, Maybe Int)
choice
genLoopIndex :: MS String
genLoopIndex :: MS String
genLoopIndex = [String] -> String -> MS String
genVarName [String
"i", String
"j", String
"k"] String
"i"
genVarNameIf :: Bool -> String -> MS String
genVarNameIf :: Bool -> String -> MS String
genVarNameIf Bool
True String
n = [String] -> String -> MS String
genVarName [] String
n
genVarNameIf Bool
False String
_ = do
String -> MS String
forall a. a -> StateT MethodState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return String
""
varNameAvailable :: String -> MS Bool
varNameAvailable :: String -> MS Bool
varNameAvailable String
n = do
Map String Int
used <- (MethodState -> Map String Int)
-> StateT MethodState Identity (Map String Int)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (MethodState
-> Getting (Map String Int) MethodState (Map String Int)
-> Map String Int
forall s a. s -> Getting a s a -> a
^. Getting (Map String Int) MethodState (Map String Int)
Lens' MethodState (Map String Int)
varNames)
Bool -> MS Bool
forall a. a -> StateT MethodState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> MS Bool) -> Bool -> MS Bool
forall a b. (a -> b) -> a -> b
$ Maybe Int -> Bool
forall a. Maybe a -> Bool
isNothing (Maybe Int -> Bool) -> Maybe Int -> Bool
forall a b. (a -> b) -> a -> b
$ String -> Map String Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup String
n Map String Int
used
ifElemError :: (Eq a) => a -> [a] -> String -> [a]
ifElemError :: forall a. Eq a => a -> [a] -> String -> [a]
ifElemError a
e [a]
es String
err = if a
e a -> [a] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [a]
es then String -> [a]
forall a. HasCallStack => String -> a
error String
err else a
e a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
es
splitVarName :: String -> (String, Maybe Int)
splitVarName :: String -> (String, Maybe Int)
splitVarName = ASetter (String, String) (String, Maybe Int) String (Maybe Int)
-> (String -> Maybe Int) -> (String, String) -> (String, Maybe Int)
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter (String, String) (String, Maybe Int) String (Maybe Int)
forall s t a b. Field2 s t a b => Lens s t a b
Lens (String, String) (String, Maybe Int) String (Maybe Int)
_2 String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe ((String, String) -> (String, Maybe Int))
-> (String -> (String, String)) -> String -> (String, Maybe Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASetter (String, String) (String, String) String String
-> (String -> String) -> (String, String) -> (String, String)
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter (String, String) (String, String) String String
Traversal (String, String) (String, String) String String
forall (r :: * -> * -> *) a b.
Bitraversable r =>
Traversal (r a a) (r b b) a b
both String -> String
forall a. [a] -> [a]
reverse ((String, String) -> (String, String))
-> (String -> (String, String)) -> String -> (String, String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, String) -> (String, String)
forall a b. (a, b) -> (b, a)
swap ((String, String) -> (String, String))
-> (String -> (String, String)) -> String -> (String, String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
span Char -> Bool
isDigit (String -> (String, String))
-> (String -> String) -> String -> (String, String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
forall a. [a] -> [a]
reverse
bumpVarName :: (String, Maybe Int) -> MS String
bumpVarName :: (String, Maybe Int) -> MS String
bumpVarName (String
n,Maybe Int
c) = do
Maybe Int
count <- (MethodState -> Maybe Int)
-> StateT MethodState Identity (Maybe Int)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (MethodState
-> Getting (Maybe Int) MethodState (Maybe Int) -> Maybe Int
forall s a. s -> Getting a s a -> a
^. ((Map String Int -> Const (Maybe Int) (Map String Int))
-> MethodState -> Const (Maybe Int) MethodState
Lens' MethodState (Map String Int)
varNames ((Map String Int -> Const (Maybe Int) (Map String Int))
-> MethodState -> Const (Maybe Int) MethodState)
-> ((Maybe Int -> Const (Maybe Int) (Maybe Int))
-> Map String Int -> Const (Maybe Int) (Map String Int))
-> Getting (Maybe Int) MethodState (Maybe Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (Map String Int)
-> Lens' (Map String Int) (Maybe (IxValue (Map String Int)))
forall m. At m => Index m -> Lens' m (Maybe (IxValue m))
at String
Index (Map String Int)
n))
let suffix :: Maybe Int
suffix = Maybe Int -> (Int -> Maybe Int) -> Maybe Int -> Maybe Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Maybe Int
count (((Int -> Int) -> Maybe Int -> Maybe Int)
-> Maybe Int -> (Int -> Int) -> Maybe Int
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Int -> Int) -> Maybe Int -> Maybe Int
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe Int
count ((Int -> Int) -> Maybe Int)
-> (Int -> Int -> Int) -> Int -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int -> Int
forall a. Ord a => a -> a -> a
max) Maybe Int
c
(MethodState -> MethodState) -> StateT MethodState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((MethodState -> MethodState) -> StateT MethodState Identity ())
-> (MethodState -> MethodState) -> StateT MethodState Identity ()
forall a b. (a -> b) -> a -> b
$ ASetter MethodState MethodState (Maybe Int) (Maybe Int)
-> Maybe Int -> MethodState -> MethodState
forall s t a b. ASetter s t a b -> b -> s -> t
set ((Map String Int -> Identity (Map String Int))
-> MethodState -> Identity MethodState
Lens' MethodState (Map String Int)
varNames ((Map String Int -> Identity (Map String Int))
-> MethodState -> Identity MethodState)
-> ((Maybe Int -> Identity (Maybe Int))
-> Map String Int -> Identity (Map String Int))
-> ASetter MethodState MethodState (Maybe Int) (Maybe Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (Map String Int)
-> Lens' (Map String Int) (Maybe (IxValue (Map String Int)))
forall m. At m => Index m -> Lens' m (Maybe (IxValue m))
at String
Index (Map String Int)
n) (Maybe Int -> MethodState -> MethodState)
-> Maybe Int -> MethodState -> MethodState
forall a b. (a -> b) -> a -> b
$ Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> Int -> Maybe Int
forall a b. (a -> b) -> a -> b
$ Int -> (Int -> Int) -> Maybe Int -> Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int
0 (Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Maybe Int
suffix
String -> MS String
forall a. a -> StateT MethodState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> MS String) -> String -> MS String
forall a b. (a -> b) -> a -> b
$ String -> (Int -> String) -> Maybe Int -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
n ((String
n String -> String -> String
forall a. [a] -> [a] -> [a]
++) (String -> String) -> (Int -> String) -> Int -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show) Maybe Int
count
setVarScope :: String -> ScopeData -> MethodState -> MethodState
setVarScope :: String -> ScopeData -> MethodState -> MethodState
setVarScope String
n ScopeData
s = ASetter
MethodState
MethodState
(Map String ScopeData)
(Map String ScopeData)
-> (Map String ScopeData -> Map String ScopeData)
-> MethodState
-> MethodState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter
MethodState
MethodState
(Map String ScopeData)
(Map String ScopeData)
Lens' MethodState (Map String ScopeData)
varScopes (String -> ScopeData -> Map String ScopeData -> Map String ScopeData
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert String
n ScopeData
s)
getVarScope :: String -> MS ScopeData
getVarScope :: String -> MS ScopeData
getVarScope String
n = do
Map String ScopeData
sMap <- (MethodState -> Map String ScopeData)
-> StateT MethodState Identity (Map String ScopeData)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (MethodState
-> Getting
(Map String ScopeData) MethodState (Map String ScopeData)
-> Map String ScopeData
forall s a. s -> Getting a s a -> a
^. Getting (Map String ScopeData) MethodState (Map String ScopeData)
Lens' MethodState (Map String ScopeData)
varScopes)
ScopeData -> MS ScopeData
forall a. a -> StateT MethodState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (ScopeData -> MS ScopeData) -> ScopeData -> MS ScopeData
forall a b. (a -> b) -> a -> b
$ case String -> Map String ScopeData -> Maybe ScopeData
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup String
n Map String ScopeData
sMap of
Maybe ScopeData
Nothing -> String -> ScopeData
forall a. HasCallStack => String -> a
error (String -> ScopeData) -> String -> ScopeData
forall a b. (a -> b) -> a -> b
$ String
"Variable with no declared scope: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
n
(Just ScopeData
scp) -> ScopeData
scp