elm/compiler/SourceSyntax/Module.hs
Evan Czaplicki c140d690fc First draft of cross-module type checking
Currently, all top-level types are imported. No alias resolution
happens so you need to use "import open M" atm.
2013-07-21 22:50:48 +02:00

49 lines
No EOL
1.5 KiB
Haskell

{-# LANGUAGE DeriveDataTypeable #-}
module SourceSyntax.Module where
import Data.Data
import Data.Binary
import Data.List (intercalate)
import qualified Data.Map as Map
import Control.Applicative ((<$>), (<*>))
import SourceSyntax.Expression
import SourceSyntax.Declaration
import SourceSyntax.Type
import System.FilePath (joinPath)
import qualified Type.Type as Type
data Module tipe var =
Module [String] Exports Imports [Declaration tipe var]
deriving (Show)
type Exports = [String]
type Imports = [(String, ImportMethod)]
data ImportMethod = As String | Importing [String] | Hiding [String]
deriving (Eq, Ord, Show, Data, Typeable)
data MetadataModule t v = MetadataModule {
names :: [String],
path :: FilePath,
exports :: [String],
imports :: [(String, ImportMethod)],
program :: LExpr t v,
types :: Map.Map String Type.Variable,
fixities :: [(Assoc, Int, String)],
aliases :: [(String, [String], Type)],
datatypes :: [ (String, [String], [(String,[Type])]) ],
foreignImports :: [(String, LExpr t v, String, Type)],
foreignExports :: [(String, String, Type)]
}
type Interfaces = Map.Map String ModuleInterface
data ModuleInterface = ModuleInterface {
iTypes :: Map.Map String Type,
iAdts :: [(String, [String], [(String,[Type])])]
} deriving Show
instance Binary ModuleInterface where
put modul = put (iTypes modul) >> put (iAdts modul)
get = ModuleInterface <$> get <*> get