module Nix.Type.Type where
import qualified Data.HashMap.Lazy as M
import Data.Text (Text)
import Nix.Utils
newtype TVar = TV String
deriving (Show, Eq, Ord)
data Type
= TVar TVar
| TCon String
| TSet Bool (AttrSet Type)
| TList [Type]
| TArr Type Type
| TMany [Type]
deriving (Show, Eq, Ord)
data Scheme = Forall [TVar] Type
deriving (Show, Eq, Ord)
typeSet :: Type
typeSet = TSet True M.empty
typeList :: Type
typeList = TList []
typeFun :: [Type] -> Type
typeFun = foldr1 TArr
typeInt, typeFloat, typeBool, typeString, typePath, typeNull :: Type
typeInt = TCon "integer"
typeFloat = TCon "float"
typeBool = TCon "boolean"
typeString = TCon "string"
typePath = TCon "path"
typeNull = TCon "null"
type Name = Text