Safe Haskell | None |
---|
Short-hands for constructing compound expressions.
- module DDC.Core.Compounds.Simple
- kRate :: Type Name
- isRateNatType :: Type Name -> Bool
- isSeriesType :: Type Name -> Bool
- isRefType :: Type Name -> Bool
- isVectorType :: Type Name -> Bool
- tTuple1 :: Type Name -> Type Name
- tTuple2 :: Type Name -> Type Name -> Type Name
- tTupleN :: [Type Name] -> Type Name
- tVector :: Type Name -> Type Name
- tSeries :: Type Name -> Type Name -> Type Name
- tSegd :: Type Name -> Type Name -> Type Name
- tSel1 :: Type Name -> Type Name -> Type Name
- tSel2 :: Type Name -> Type Name -> Type Name -> Type Name
- tRef :: Type Name -> Type Name
- tWorld :: Type Name
- tRateNat :: Type Name -> Type Name
- tDown :: Int -> Type Name -> Type Name
- tTail :: Int -> Type Name -> Type Name
- tProcess :: Type Name
- tVoid :: Type Name
- tBool :: Type Name
- tNat :: Type Name
- tInt :: Type Name
- tWord :: Int -> Type Name
- tFloat :: Int -> Type Name
- tVec :: Int -> Type Name -> Type Name
- xBool :: Bool -> Exp a Name
- dcBool :: Bool -> DaCon Name
- xNat :: Integer -> Exp a Name
- dcNat :: Integer -> DaCon Name
- dcTuple1 :: DaCon Name
- xTuple2 :: Type Name -> Type Name -> Exp a Name -> Exp a Name -> Exp a Name
- dcTuple2 :: DaCon Name
- dcTupleN :: Int -> DaCon Name
- xvRep :: Int -> Type Name -> Exp () Name -> Exp () Name
- xvProj :: Int -> Int -> Type Name -> Exp () Name -> Exp () Name
- xvGather :: Int -> Type Name -> Exp () Name -> Exp () Name -> Exp () Name
- xvScatter :: Int -> Type Name -> Exp () Name -> Exp () Name -> Exp () Name -> Exp () Name
- xProj :: [Type Name] -> Int -> Exp () Name -> Exp () Name
- xRateOfSeries :: TypeF -> TypeF -> ExpF -> ExpF
- xNatOfRateNat :: TypeF -> ExpF -> ExpF
- xNext :: TypeF -> TypeF -> ExpF -> ExpF -> ExpF
- xNextC :: Int -> TypeF -> TypeF -> ExpF -> ExpF -> ExpF
- xDown :: Int -> TypeF -> TypeF -> ExpF -> ExpF -> ExpF
- xTail :: Int -> TypeF -> TypeF -> ExpF -> ExpF -> ExpF
- xLoopN :: TypeF -> ExpF -> ExpF -> ExpF
- xGuard :: ExpF -> ExpF -> ExpF -> ExpF
- xSegment :: ExpF -> ExpF -> ExpF -> ExpF
- xSplit :: Int -> TypeF -> ExpF -> ExpF -> ExpF -> ExpF
- xNew :: Type Name -> Exp () Name -> Exp () Name
- xRead :: Type Name -> Exp () Name -> Exp () Name
- xWrite :: Type Name -> Exp () Name -> Exp () Name -> Exp () Name
- xNewVector :: Type Name -> Exp () Name -> Exp () Name
- xNewVectorR :: Type Name -> Type Name -> Exp () Name
- xNewVectorN :: Type Name -> Type Name -> Exp () Name -> Exp () Name
- xReadVector :: Type Name -> Exp () Name -> Exp () Name -> Exp () Name
- xReadVectorC :: Int -> Type Name -> Exp () Name -> Exp () Name -> Exp () Name
- xWriteVector :: Type Name -> Exp () Name -> Exp () Name -> Exp () Name -> Exp () Name
- xWriteVectorC :: Int -> Type Name -> Exp () Name -> Exp () Name -> Exp () Name -> Exp () Name
- xTailVector :: Int -> Type Name -> Type Name -> Exp () Name -> Exp () Name -> Exp () Name
- xTruncVector :: Type Name -> Exp () Name -> Exp () Name -> Exp () Name
Documentation
module DDC.Core.Compounds.Simple
Fragment specific kinds
Fragment specific types
isRateNatType :: Type Name -> BoolSource
Check if some type is a fully applied type of a RateNat
isSeriesType :: Type Name -> BoolSource
Check if some type is a fully applied type of a Series.
isVectorType :: Type Name -> BoolSource
Check is some type is a fully applied type of a Vector.
Primtiive types
Primitive literals and data constructors
xTuple2 :: Type Name -> Type Name -> Exp a Name -> Exp a Name -> Exp a NameSource
Construct a Tuple2#
Primitive Vec operators
Series operators
xRateOfSeries :: TypeF -> TypeF -> ExpF -> ExpFSource
xNatOfRateNat :: TypeF -> ExpF -> ExpFSource