module Language.Futhark.Semantic
( ImportName
, mkInitialImport
, mkImportFrom
, includeToFilePath
, includeToString
, FileModule(..)
, Imports
, Namespace(..)
, Env(..)
, TySet
, FunSig(..)
, NameMap
, BoundV(..)
, Mod(..)
, TypeBinding(..)
, MTy(..)
)
where
import Data.Loc
import qualified Data.Map.Strict as M
import qualified System.FilePath.Posix as Posix
import qualified System.FilePath as Native
import Prelude hiding (mod)
import Language.Futhark
import Futhark.Util (dropLast, toPOSIX, fromPOSIX)
import Futhark.Util.Pretty
data ImportName = ImportName Posix.FilePath SrcLoc
deriving (Eq, Ord, Show)
instance Located ImportName where
locOf (ImportName _ loc) = locOf loc
mkInitialImport :: Native.FilePath -> ImportName
mkInitialImport s = ImportName (Posix.normalise $ toPOSIX s) noLoc
mkImportFrom :: ImportName -> String -> SrcLoc -> ImportName
mkImportFrom (ImportName includer _) includee
| Posix.isAbsolute includee = ImportName includee
| otherwise = ImportName $ Posix.normalise $ Posix.joinPath $ includer' ++ includee'
where (dotdots, includee') = span ("../"==) $ Posix.splitPath includee
includer_parts = init $ Posix.splitPath includer
includer'
| length dotdots > length includer_parts =
replicate (length dotdots - length includer_parts) "../"
| otherwise =
dropLast (length dotdots) includer_parts
includeToFilePath :: ImportName -> Native.FilePath
includeToFilePath (ImportName s _) = fromPOSIX $ Posix.normalise s Posix.<.> "fut"
includeToString :: ImportName -> String
includeToString (ImportName s _) = Posix.normalise $ Posix.makeRelative "/" s
data FileModule = FileModule { fileAbs :: TySet
, fileEnv :: Env
, fileProg :: Prog
}
type Imports = [(String, FileModule)]
data Namespace = Term
| Type
| Signature
deriving (Eq, Ord, Show, Enum)
type TySet = M.Map (QualName VName) Liftedness
data Mod = ModEnv Env
| ModFun FunSig
deriving (Show)
data FunSig = FunSig { funSigAbs :: TySet
, funSigMod :: Mod
, funSigMty :: MTy
}
deriving (Show)
data MTy = MTy { mtyAbs :: TySet
, mtyMod :: Mod
}
deriving (Show)
data TypeBinding = TypeAbbr Liftedness [TypeParam] StructType
deriving (Eq, Show)
data BoundV = BoundV [TypeParam] StructType
deriving (Show)
type NameMap = M.Map (Namespace, Name) (QualName VName)
data Env = Env { envVtable :: M.Map VName BoundV
, envTypeTable :: M.Map VName TypeBinding
, envSigTable :: M.Map VName MTy
, envModTable :: M.Map VName Mod
, envNameMap :: NameMap
} deriving (Show)
instance Semigroup Env where
Env vt1 tt1 st1 mt1 nt1 <> Env vt2 tt2 st2 mt2 nt2 =
Env (vt1<>vt2) (tt1<>tt2) (st1<>st2) (mt1<>mt2) (nt1<>nt2)
instance Monoid Env where
mempty = Env mempty mempty mempty mempty mempty
instance Pretty MTy where
ppr = ppr . mtyMod
instance Pretty Mod where
ppr (ModEnv e) = ppr e
ppr (ModFun (FunSig _ mod mty)) = ppr mod <+> text "->" </> ppr mty
instance Pretty Env where
ppr (Env vtable ttable sigtable modtable _) =
nestedBlock "{" "}" $ stack $ punctuate line $ concat
[map renderTypeBind (M.toList ttable),
map renderValBind (M.toList vtable),
map renderModType (M.toList sigtable),
map renderMod (M.toList modtable)]
where renderTypeBind (name, TypeAbbr l tps tp) =
p l <+> pprName name <> mconcat (map ((text " "<>) . ppr) tps) <>
text " =" <+> ppr tp
where p Lifted = text "type^"
p Unlifted = text "type"
renderValBind (name, BoundV tps t) =
text "val" <+> pprName name <> mconcat (map ((text " "<>) . ppr) tps) <>
text " =" <+> ppr t
renderModType (name, _sig) =
text "module type" <+> pprName name
renderMod (name, mod) =
text "module" <+> pprName name <> text " =" <+> ppr mod