symantic-lib-0.0.2.20170703: Symantics for common types.

Safe HaskellNone
LanguageHaskell2010

Language.Symantic.Lib.NonNull

Contents

Description

Symantic for NonNull.

Synopsis

Class Sym_NonNull

class Sym_NonNull term where Source #

Methods

fromNullable :: MonoFoldable o => term o -> term (Maybe (NonNull o)) Source #

toNullable :: MonoFoldable o => term (NonNull o) -> term o Source #

ncons :: SemiSequence s => term (Element s) -> term s -> term (NonNull s) Source #

nuncons :: IsSequence s => term (NonNull s) -> term (Element s, Maybe (NonNull s)) Source #

head :: MonoFoldable o => term (NonNull o) -> term (Element o) Source #

last :: MonoFoldable o => term (NonNull o) -> term (Element o) Source #

tail :: IsSequence s => term (NonNull s) -> term s Source #

init :: IsSequence s => term (NonNull s) -> term s Source #

nfilter :: IsSequence s => term (Element s -> Bool) -> term (NonNull s) -> term s Source #

fromNullable :: Sym_NonNull (UnT term) => Trans term => MonoFoldable o => term o -> term (Maybe (NonNull o)) Source #

toNullable :: Sym_NonNull (UnT term) => Trans term => MonoFoldable o => term (NonNull o) -> term o Source #

ncons :: Sym_NonNull (UnT term) => Trans term => SemiSequence s => term (Element s) -> term s -> term (NonNull s) Source #

nuncons :: Sym_NonNull (UnT term) => Trans term => IsSequence s => term (NonNull s) -> term (Element s, Maybe (NonNull s)) Source #

head :: Sym_NonNull (UnT term) => Trans term => MonoFoldable o => term (NonNull o) -> term (Element o) Source #

last :: Sym_NonNull (UnT term) => Trans term => MonoFoldable o => term (NonNull o) -> term (Element o) Source #

tail :: Sym_NonNull (UnT term) => Trans term => IsSequence s => term (NonNull s) -> term s Source #

init :: Sym_NonNull (UnT term) => Trans term => IsSequence s => term (NonNull s) -> term s Source #

nfilter :: Sym_NonNull (UnT term) => Trans term => IsSequence s => term (Element s -> Bool) -> term (NonNull s) -> term s Source #

Instances

Sym_NonNull Eval Source # 
Sym_NonNull View Source # 
(Sym_NonNull term, Sym_Lambda term) => Sym_NonNull (BetaT term) Source # 

Methods

fromNullable :: MonoFoldable o => BetaT term o -> BetaT term (Maybe (NonNull o)) Source #

toNullable :: MonoFoldable o => BetaT term (NonNull o) -> BetaT term o Source #

ncons :: SemiSequence s => BetaT term (Element s) -> BetaT term s -> BetaT term (NonNull s) Source #

nuncons :: IsSequence s => BetaT term (NonNull s) -> BetaT term (Element s, Maybe (NonNull s)) Source #

head :: MonoFoldable o => BetaT term (NonNull o) -> BetaT term (Element o) Source #

last :: MonoFoldable o => BetaT term (NonNull o) -> BetaT term (Element o) Source #

tail :: IsSequence s => BetaT term (NonNull s) -> BetaT term s Source #

init :: IsSequence s => BetaT term (NonNull s) -> BetaT term s Source #

nfilter :: IsSequence s => BetaT term (Element s -> Bool) -> BetaT term (NonNull s) -> BetaT term s Source #

(Sym_NonNull r1, Sym_NonNull r2) => Sym_NonNull (Dup r1 r2) Source # 

Methods

fromNullable :: MonoFoldable o => Dup r1 r2 o -> Dup r1 r2 (Maybe (NonNull o)) Source #

toNullable :: MonoFoldable o => Dup r1 r2 (NonNull o) -> Dup r1 r2 o Source #

ncons :: SemiSequence s => Dup r1 r2 (Element s) -> Dup r1 r2 s -> Dup r1 r2 (NonNull s) Source #

nuncons :: IsSequence s => Dup r1 r2 (NonNull s) -> Dup r1 r2 (Element s, Maybe (NonNull s)) Source #

head :: MonoFoldable o => Dup r1 r2 (NonNull o) -> Dup r1 r2 (Element o) Source #

last :: MonoFoldable o => Dup r1 r2 (NonNull o) -> Dup r1 r2 (Element o) Source #

tail :: IsSequence s => Dup r1 r2 (NonNull s) -> Dup r1 r2 s Source #

init :: IsSequence s => Dup r1 r2 (NonNull s) -> Dup r1 r2 s Source #

nfilter :: IsSequence s => Dup r1 r2 (Element s -> Bool) -> Dup r1 r2 (NonNull s) -> Dup r1 r2 s Source #

Types

tyNonNull :: Source src => Type src vs a -> Type src vs (NonNull a) Source #

Terms

teNonNull_nfilter :: TermDef NonNull '[Proxy s, Proxy e] ((IsSequence s # (e #~ Element s)) #> ((e -> Bool) -> NonNull s -> s)) Source #

Orphan instances

ClassInstancesFor (* -> *) NonNull Source # 

Methods

proveConstraintFor :: Source src => proxy c -> Type Constraint src vs q -> Maybe (Qual q) #

TypeInstancesFor (* -> *) NonNull Source # 

Methods

expandFamFor :: Source src => proxy c -> Len Type vs -> Const kt src fam -> Types src vs ts -> Maybe (Type kt src vs (Fam kt fam ts)) #

NameTyOf (* -> *) NonNull Source # 

Methods

nameTyOf :: proxy c -> Mod NameTy #

isNameTyOp :: proxy c -> Bool #

FixityOf (* -> *) NonNull Source # 

Methods

fixityOf :: proxy c -> Maybe Fixity #

(Source src, SymInj (* -> *) ss NonNull) => ModuleFor (* -> *) src ss NonNull Source # 

Methods

moduleFor :: (PathMod, Module ss NonNull) #

Gram_Term_AtomsFor (* -> *) src ss g NonNull Source # 

Methods

g_term_atomsFor :: [CF NonNull (AST_Term ss g)] #