symantic-6.3.2.20180208: Library for Typed Tagless-Final Higher-Order Composable DSL

Safe HaskellNone
LanguageHaskell2010

Language.Symantic.Typing.Module

Contents

Synopsis

Type NsT

data NsT Source #

Constructors

NsTerm 
NsType 

Type Name

type Name = Text Source #

Type NameTy

newtype NameTy Source #

Name of a Type.

Constructors

NameTy Text 
Instances
Eq NameTy Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

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

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

Ord NameTy Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Show NameTy Source # 
Instance details

Defined in Language.Symantic.Typing.Module

IsString NameTy Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

fromString :: String -> NameTy #

Type NameConst

type NameConst = NameTy Source #

Name of a Const.

Type NameFam

type NameFam = NameTy Source #

Name of a Fam.

Class NameOf

class NameOf a where Source #

Minimal complete definition

nameOf

Methods

nameOf :: a -> Name Source #

Instances
NameOf NameTe Source # 
Instance details

Defined in Language.Symantic.Compiling.Module

Methods

nameOf :: NameTe -> Name Source #

Class NameTyOf

class NameTyOf (c :: kc) where Source #

Return the NameTy of something.

Methods

nameTyOf :: proxy c -> Mod NameTy Source #

nameTyOf :: Typeable c => proxy c -> Mod NameTy Source #

isNameTyOp :: proxy c -> Bool Source #

isNameTyOp :: Typeable c => proxy c -> Bool Source #

Instances
NameTyOf () Source # 
Instance details

Defined in Language.Symantic.Typing.Type

Methods

nameTyOf :: proxy () -> Mod NameTy Source #

isNameTyOp :: proxy () -> Bool Source #

NameTyOf (#>) Source # 
Instance details

Defined in Language.Symantic.Typing.Type

Methods

nameTyOf :: proxy (#>) -> Mod NameTy Source #

isNameTyOp :: proxy (#>) -> Bool Source #

NameTyOf (#) Source # 
Instance details

Defined in Language.Symantic.Typing.Type

Methods

nameTyOf :: proxy (#) -> Mod NameTy Source #

isNameTyOp :: proxy (#) -> Bool Source #

NameTyOf ((#~) :: k -> k -> Constraint) Source # 
Instance details

Defined in Language.Symantic.Typing.Type

Methods

nameTyOf :: proxy (#~) -> Mod NameTy Source #

isNameTyOp :: proxy (#~) -> Bool Source #

Type Mod

data Mod a Source #

PathMod of something.

Constructors

Mod PathMod a 
Instances
Functor Mod Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

fmap :: (a -> b) -> Mod a -> Mod b #

(<$) :: a -> Mod b -> Mod a #

Eq a => Eq (Mod a) Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

(==) :: Mod a -> Mod a -> Bool #

(/=) :: Mod a -> Mod a -> Bool #

Ord a => Ord (Mod a) Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

compare :: Mod a -> Mod a -> Ordering #

(<) :: Mod a -> Mod a -> Bool #

(<=) :: Mod a -> Mod a -> Bool #

(>) :: Mod a -> Mod a -> Bool #

(>=) :: Mod a -> Mod a -> Bool #

max :: Mod a -> Mod a -> Mod a #

min :: Mod a -> Mod a -> Mod a #

Show a => Show (Mod a) Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

showsPrec :: Int -> Mod a -> ShowS #

show :: Mod a -> String #

showList :: [Mod a] -> ShowS #

Type PathMod

type PathMod = [NameMod] Source #

Path to a Module.

Type NameMod

newtype NameMod Source #

Name of Module.

Constructors

NameMod Name 

Type Imports

newtype Imports name Source #

Map PathMods of Names.

Constructors

Imports (Map PathMod (MapFixity (Map name PathMod))) 
Instances
Eq name => Eq (Imports name) Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

(==) :: Imports name -> Imports name -> Bool #

(/=) :: Imports name -> Imports name -> Bool #

Show name => Show (Imports name) Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

showsPrec :: Int -> Imports name -> ShowS #

show :: Imports name -> String #

showList :: [Imports name] -> ShowS #

Ord name => Semigroup (Imports name) Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

(<>) :: Imports name -> Imports name -> Imports name #

sconcat :: NonEmpty (Imports name) -> Imports name #

stimes :: Integral b => b -> Imports name -> Imports name #

Ord name => Monoid (Imports name) Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

mempty :: Imports name #

mappend :: Imports name -> Imports name -> Imports name #

mconcat :: [Imports name] -> Imports name #

lookupImports :: Ord name => Fixy p i q a -> Mod name -> Imports name -> Maybe PathMod Source #

revlookupImports :: Ord name => Fixy p i q a -> Mod name -> Imports name -> Maybe PathMod Source #

Class ImportTypes

class ImportTypes ts where Source #

Minimal complete definition

importTypes

Instances
ImportTypes ([] :: [k]) Source # 
Instance details

Defined in Language.Symantic.Typing.Module

(NameTyOf t, FixityOf t, ImportTypes ts) => ImportTypes (Proxy t ': ts :: [*]) Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Type Fixy

data Fixy p i q a where Source #

Constructors

FixyPrefix :: Fixy p i q p 
FixyInfix :: Fixy p i q i 
FixyPostfix :: Fixy p i q q 
Instances
Eq (Fixy p i q a) Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

(==) :: Fixy p i q a -> Fixy p i q a -> Bool #

(/=) :: Fixy p i q a -> Fixy p i q a -> Bool #

Show (Fixy p i q a) Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

showsPrec :: Int -> Fixy p i q a -> ShowS #

show :: Fixy p i q a -> String #

showList :: [Fixy p i q a] -> ShowS #

Class FixityOf

class FixityOf (c :: kc) where Source #

Return the Fixity of something.

Methods

fixityOf :: proxy c -> Maybe Fixity Source #

Instances
FixityOf (c :: Type) Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

fixityOf :: proxy c -> Maybe Fixity Source #

FixityOf (c :: Constraint) Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

fixityOf :: proxy c -> Maybe Fixity Source #

FixityOf (#>) Source # 
Instance details

Defined in Language.Symantic.Typing.Type

Methods

fixityOf :: proxy (#>) -> Maybe Fixity Source #

FixityOf (#) Source # 
Instance details

Defined in Language.Symantic.Typing.Type

Methods

fixityOf :: proxy (#) -> Maybe Fixity Source #

FixityOf ((#~) :: k -> k -> Constraint) Source # 
Instance details

Defined in Language.Symantic.Typing.Type

Methods

fixityOf :: proxy (#~) -> Maybe Fixity Source #

FixityOf ((->) :: * -> * -> *) Source # 
Instance details

Defined in Language.Symantic.Typing.Type

Methods

fixityOf :: proxy (->) -> Maybe Fixity Source #

Type FixyA

newtype FixyA Source #

Like Fixy, but when all choices have the same type.

Constructors

FixyA (forall (a :: *). Fixy a a a a) 
Instances
Eq FixyA Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

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

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

Show FixyA Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

showsPrec :: Int -> FixyA -> ShowS #

show :: FixyA -> String #

showList :: [FixyA] -> ShowS #

Type WithFixity

data WithFixity a Source #

Constructors

WithFixity a Fixity 
Instances
Functor WithFixity Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

fmap :: (a -> b) -> WithFixity a -> WithFixity b #

(<$) :: a -> WithFixity b -> WithFixity a #

Eq a => Eq (WithFixity a) Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

(==) :: WithFixity a -> WithFixity a -> Bool #

(/=) :: WithFixity a -> WithFixity a -> Bool #

Show a => Show (WithFixity a) Source # 
Instance details

Defined in Language.Symantic.Typing.Module

IsString a => IsString (WithFixity a) Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

fromString :: String -> WithFixity a #

Type ByFixity

data ByFixity p i q Source #

Fixity namespace.

Constructors

ByFixity 

Fields

Instances
(Eq p, Eq i, Eq q) => Eq (ByFixity p i q) Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

(==) :: ByFixity p i q -> ByFixity p i q -> Bool #

(/=) :: ByFixity p i q -> ByFixity p i q -> Bool #

(Show p, Show i, Show q) => Show (ByFixity p i q) Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

showsPrec :: Int -> ByFixity p i q -> ShowS #

show :: ByFixity p i q -> String #

showList :: [ByFixity p i q] -> ShowS #

(Semigroup p, Semigroup i, Semigroup q) => Semigroup (ByFixity p i q) Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

(<>) :: ByFixity p i q -> ByFixity p i q -> ByFixity p i q #

sconcat :: NonEmpty (ByFixity p i q) -> ByFixity p i q #

stimes :: Integral b => b -> ByFixity p i q -> ByFixity p i q #

(Monoid p, Monoid i, Monoid q) => Monoid (ByFixity p i q) Source # 
Instance details

Defined in Language.Symantic.Typing.Module

Methods

mempty :: ByFixity p i q #

mappend :: ByFixity p i q -> ByFixity p i q -> ByFixity p i q #

mconcat :: [ByFixity p i q] -> ByFixity p i q #

getByFixity :: Fixy p i q a -> MapFixity b -> b Source #

selectByFixity :: Fixy p i q a -> ByFixity p i q -> a Source #

Type MapFixity

type MapFixity a = ByFixity a a a Source #

Like ByFixity, but with the same type parameter.

mapMapFixity :: (a -> b) -> MapFixity a -> MapFixity b Source #