hnix-0.16.0: Haskell implementation of the Nix language
Safe HaskellNone
LanguageHaskell2010

Nix.Type.Type

Description

The basis of the Nix type system (type-level). Based on the Hindley–Milner type system. Therefore -> from this the type inference follows.

Synopsis

Documentation

newtype TVar Source #

Hindrey-Milner type interface

Type variable in the Nix type system.

Constructors

TV Text 

Instances

Instances details
Eq TVar Source # 
Instance details

Defined in Nix.Type.Type

Methods

(==) :: TVar -> TVar -> Bool #

(/=) :: TVar -> TVar -> Bool #

Ord TVar Source # 
Instance details

Defined in Nix.Type.Type

Methods

compare :: TVar -> TVar -> Ordering #

(<) :: TVar -> TVar -> Bool #

(<=) :: TVar -> TVar -> Bool #

(>) :: TVar -> TVar -> Bool #

(>=) :: TVar -> TVar -> Bool #

max :: TVar -> TVar -> TVar #

min :: TVar -> TVar -> TVar #

Show TVar Source # 
Instance details

Defined in Nix.Type.Type

Methods

showsPrec :: Int -> TVar -> ShowS #

show :: TVar -> String #

showList :: [TVar] -> ShowS #

data Type Source #

The basic type definitions in the Nix type system (type-level code).

Constructors

TVar TVar

Type variable in the Nix type system.

TCon Text

Concrete (non-polymorphic, constant) type in the Nix type system.

TSet Variadic (AttrSet Type)

Heterogeneous map in the Nix type system. True -> variadic.

TList [Type]

Heterogeneous list in the Nix type system.

(:~>) Type Type infixr 1

Type arrow (Type -> Type) in the Nix type system.

TMany [Type]

Variant type (term). Since relating to Nix type system, more precicely - dynamic types in dynamicly typed language (which is Nix).

Instances

Instances details
Eq Type Source # 
Instance details

Defined in Nix.Type.Type

Methods

(==) :: Type -> Type -> Bool #

(/=) :: Type -> Type -> Bool #

Ord Type Source # 
Instance details

Defined in Nix.Type.Type

Methods

compare :: Type -> Type -> Ordering #

(<) :: Type -> Type -> Bool #

(<=) :: Type -> Type -> Bool #

(>) :: Type -> Type -> Bool #

(>=) :: Type -> Type -> Bool #

max :: Type -> Type -> Type #

min :: Type -> Type -> Type #

Show Type Source # 
Instance details

Defined in Nix.Type.Type

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

data Scheme Source #

Hindley–Milner type system uses "scheme" term for "polytypes". Types containing forall quantifiers: forall a . a. Note: HM allows only top-level forall quantification, so no RankNTypes in it.

Constructors

Forall [TVar] Type

Forall [TVar] Type: the Nix type system forall vars. type.

Instances

Instances details
Eq Scheme Source # 
Instance details

Defined in Nix.Type.Type

Methods

(==) :: Scheme -> Scheme -> Bool #

(/=) :: Scheme -> Scheme -> Bool #

Ord Scheme Source # 
Instance details

Defined in Nix.Type.Type

Show Scheme Source # 
Instance details

Defined in Nix.Type.Type

typeNull :: Type Source #

Concrete types in the Nix type system.

typeBool :: Type Source #

Concrete types in the Nix type system.

typeInt :: Type Source #

Concrete types in the Nix type system.

typeFloat :: Type Source #

Concrete types in the Nix type system.

typeString :: Type Source #

Concrete types in the Nix type system.

typePath :: Type Source #

Concrete types in the Nix type system.