| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Infernu.Fix
Documentation
Instances
| Substable Type | applySubst for Types >>> applySubst (Map.fromList [(0, Fix $ TBody TNumber)]) (Fix $ TBody $ TVar 0) Fix (TBody TNumber) >>> applySubst (Map.fromList [(0, Fix $ TRow $ TRowEnd Nothing)]) (Fix $ TBody $ TVar 0) Fix (TRow (TRowEnd Nothing)) >>> applySubst (Map.fromList [(0, Fix $ TRow $ TRowEnd Nothing)]) (Fix $ TRow $ TRowEnd $ Just $ RowTVar 0) Fix (TRow (TRowEnd Nothing)) >>> applySubst (Map.fromList [(0, Fix $ TRow $ TRowEnd Nothing)]) (Fix $ TRow $ TRowProp "bla" (schemeEmpty $ Fix $ TBody TString) (TRowEnd $ Just $ RowTVar 0)) Fix (TRow (TRowProp "bla" (TScheme {schemeVars = [], schemeType = TQual {qualPred = [], qualType = Fix (TBody TString)}}) (TRowEnd Nothing))) |
| VarNames Type | VarNames instance for Type t
|
| Pretty Type | |
| Eq (f (Fix f)) => Eq (Fix f) | |
| Ord (f (Fix f)) => Ord (Fix f) | |
| Show (f (Fix f)) => Show (Fix f) | |
| Substable (TRowList Type) | |
| VarNames (FType (Fix FType)) | |
| Pretty [Type] | |
| Pretty (FType Type) |
fmapReplace :: (Functor f, Eq (f a)) => (f a -> f b -> a -> b) -> f a -> f b -> f a -> f b Source
fixToList :: Foldable t => Fix t -> [Fix t] Source
Flattens a fix-type to a list of all tree nodes
>>>fixToList $ (Fix $ TCons TArray [Fix $ TCons TArray [Fix $ TBody TNumber]])[Fix (TCons TArray [Fix (TCons TArray [Fix (TBody TNumber)])]),Fix (TCons TArray [Fix (TBody TNumber)]),Fix (TBody TNumber)]>>>fixToList $ (Fix $ TRow $ TRowProp "x" (TScheme [] $ Fix $ TBody TNumber) (TRowEnd Nothing))[Fix (TRow (TRowProp "x" (TScheme {schemeVars = [], schemeType = Fix (TBody TNumber)}) (TRowEnd Nothing))),Fix (TBody TNumber)]