module Language.Clafer.Common where
import Data.Tree
import Data.Maybe
import Data.Char
import Data.List
import qualified Data.Map as Map
import Language.Clafer.Front.Absclafer
import Language.Clafer.Intermediate.Intclafer
type Result = String
transIdent :: PosIdent -> Result
transIdent x = case x of
PosIdent str -> snd str
mkIdent :: String -> PosIdent
mkIdent str = PosIdent ((0, 0), str)
mkInteger :: Read a => PosInteger -> a
mkInteger (PosInteger (_, n)) = read n
type Ident = PosIdent
getSuper :: IClafer -> String
getSuper = getSuperId._supers._super
getSuperNoArr :: IClafer -> String
getSuperNoArr clafer
| _isOverlapping $ _super clafer = "clafer"
| otherwise = getSuper clafer
getSuperId :: [PExp] -> String
getSuperId = _sident . Language.Clafer.Intermediate.Intclafer._exp . head
isEqClaferId :: String -> IClafer -> Bool
isEqClaferId = flip $ (==)._uid
idToPExp :: String -> Span -> String -> String -> Bool -> PExp
idToPExp pid' pos modids id' isTop' = PExp (Just $ TClafer [id']) pid' pos (IClaferId modids id' isTop')
mkLClaferId :: String -> Bool -> IExp
mkLClaferId = IClaferId ""
mkPLClaferId :: String -> Bool -> PExp
mkPLClaferId id' isTop' = pExpDefPidPos $ mkLClaferId id' isTop'
pExpDefPidPos :: IExp -> PExp
pExpDefPidPos = pExpDefPid noSpan
pExpDefPid :: Span -> IExp -> PExp
pExpDefPid = pExpDef ""
pExpDef :: String -> Span -> IExp -> PExp
pExpDef = PExp Nothing
isParent :: PExp -> Bool
isParent (PExp _ _ _ (IClaferId _ id' _)) = id' == parent
isParent _ = False
isClaferName :: PExp -> Bool
isClaferName (PExp _ _ _ (IClaferId _ id' _)) =
id' `notElem` ([this, parent, children, ref] ++ primitiveTypes)
isClaferName _ = False
isClaferName' :: PExp -> Bool
isClaferName' (PExp _ _ _ (IClaferId _ _ _)) = True
isClaferName' _ = False
getClaferName :: PExp -> String
getClaferName (PExp _ _ _ (IClaferId _ id' _)) = id'
getClaferName _ = ""
elemToClafer :: IElement -> Maybe IClafer
elemToClafer x = case x of
IEClafer clafer -> Just clafer
_ -> Nothing
toClafers :: [IElement] -> [IClafer]
toClafers = mapMaybe elemToClafer
mapHierarchy :: (IClafer -> b)
-> (IClafer -> String)
-> [IClafer]
-> IClafer
-> [b]
mapHierarchy f sf = (map f.).(findHierarchy sf)
findHierarchy :: (IClafer -> String)
-> [IClafer]
-> IClafer
-> [IClafer]
findHierarchy sFun clafers clafer
| sFun clafer == "clafer" = [clafer]
| otherwise = if clafer `elem` superClafers
then error $ "Inheritance hierarchy contains a cycle: line " ++ (show $ _cinPos clafer)
else clafer : superClafers
where
superClafers = unfoldr (\c -> find (isEqClaferId $ sFun c) clafers >>=
Just . (apply id)) clafer
apply :: forall t t1. (t -> t1) -> t -> (t, t1)
apply f x = (x, f x)
bfs :: forall b b1. (b1 -> (b, [b1])) -> [b1] -> [b]
bfs toNode seed = map rootLabel $ concat $ takeWhile (not.null) $
iterate (concatMap subForest) $ unfoldForest toNode seed
toNodeShallow :: IClafer -> (IClafer, [IClafer])
toNodeShallow = apply (getSubclafers._elements)
getSubclafers :: [IElement] -> [IClafer]
getSubclafers = mapMaybe elemToClafer
bfsClafers :: [IClafer] -> [IClafer]
bfsClafers clafers = bfs toNodeShallow clafers
lurry :: forall t t1. ([t1] -> t) -> t1 -> t1 -> t
lurry f x y = f [x,y]
fst3 :: forall t t1 t2. (t, t1, t2) -> t
fst3 (a, _, _) = a
snd3 :: forall t t1 t2. (t, t1, t2) -> t1
snd3 (_, b, _) = b
trd3 :: forall t t1 t2. (t, t1, t2) -> t2
trd3 (_, _, c) = c
toTriple :: forall t t1 t2. t -> (t1, t2) -> (t, t1, t2)
toTriple a (b,c) = (a, b, c)
toMTriple :: forall t t1 t2. t -> (t1, t2) -> Maybe (t, t1, t2)
toMTriple a (b,c) = Just (a, b, c)
iNot :: String
iNot = "!"
iCSet :: String
iCSet = "#"
iMin :: String
iMin = "-"
iGMax :: String
iGMax = "max"
iGMin :: String
iGMin = "min"
iSumSet :: String
iSumSet = "sum"
unOps :: [String]
unOps = [iNot, iCSet, iMin, iGMax, iGMin, iSumSet]
iIff :: String
iIff = "<=>"
iImpl :: String
iImpl = "=>"
iOr :: String
iOr = "||"
iXor :: String
iXor = "xor"
iAnd :: String
iAnd = "&&"
logBinOps :: [String]
logBinOps = [iIff, iImpl, iOr, iXor, iAnd]
iLt :: String
iLt = "<"
iGt :: String
iGt = ">"
iEq :: String
iEq = "="
iLte :: String
iLte = "<="
iGte :: String
iGte = ">="
iNeq :: String
iNeq = "!="
iIn :: String
iIn = "in"
iNin :: String
iNin = "not in"
relGenBinOps :: [String]
relGenBinOps = [iLt, iGt, iEq, iLte, iGte, iNeq]
relSetBinOps :: [String]
relSetBinOps = [iIn, iNin]
relBinOps :: [String]
relBinOps = relGenBinOps ++ relSetBinOps
iPlus :: String
iPlus = "+"
iSub :: String
iSub = "-"
iMul :: String
iMul = "*"
iDiv :: String
iDiv = "/"
iSumSet' :: String
iSumSet' = "sum'"
arithBinOps :: [String]
arithBinOps = [iPlus, iSub, iMul, iDiv, iSumSet']
iUnion :: String
iUnion = "++"
iDifference :: String
iDifference = "--"
iIntersection :: String
iIntersection = "&"
iDomain :: String
iDomain = "<:"
iRange :: String
iRange = ":>"
iJoin :: String
iJoin = "."
setBinOps :: [String]
setBinOps = [iUnion, iDifference, iIntersection, iDomain, iRange, iJoin]
binOps :: [String]
binOps = logBinOps ++ relBinOps ++ arithBinOps ++ setBinOps
iIfThenElse :: String
iIfThenElse = "=>else"
mkIFunExp :: String -> [IExp] -> IExp
mkIFunExp _ (x:[]) = x
mkIFunExp op' xs = foldl1 (\x y -> IFunExp op' $ map (PExp (Just $ TClafer []) "" noSpan) [x,y]) xs
toLowerS :: String -> String
toLowerS "" = ""
toLowerS (s:ss) = toLower s : ss
this :: String
this = "this"
parent :: String
parent = "parent"
children :: String
children = "children"
ref :: String
ref = "ref"
specialNames :: [String]
specialNames = [this, parent, children, ref]
strType :: String
strType = "string"
intType :: String
intType = "int"
integerType :: String
integerType = "integer"
realType :: String
realType = "real"
baseClafer :: String
baseClafer = "clafer"
modSep :: String
modSep = "\\"
primitiveTypes :: [String]
primitiveTypes = [strType, intType, integerType, realType]
isPrimitive :: String -> Bool
isPrimitive = flip elem primitiveTypes
data GEnv = GEnv {
identCountMap :: Map.Map String Int,
expCount :: Int,
stable :: Map.Map UID [[UID]],
sClafers ::[IClafer]
} deriving (Eq, Show)
voidf :: Monad m => m t -> m ()
voidf f = do
_ <- f
return ()