Copyright | disco team and contributors |
---|---|
Maintainer | byorgey@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Disco.Syntax.Prims
Description
Concrete syntax for the prims (i.e. built-in constants) supported by the language.
Synopsis
- data Prim where
- PrimUOp :: UOp -> Prim
- PrimBOp :: BOp -> Prim
- PrimLeft :: Prim
- PrimRight :: Prim
- PrimSqrt :: Prim
- PrimFloor :: Prim
- PrimCeil :: Prim
- PrimAbs :: Prim
- PrimMin :: Prim
- PrimMax :: Prim
- PrimPower :: Prim
- PrimList :: Prim
- PrimBag :: Prim
- PrimSet :: Prim
- PrimB2C :: Prim
- PrimC2B :: Prim
- PrimUC2B :: Prim
- PrimMapToSet :: Prim
- PrimSetToMap :: Prim
- PrimSummary :: Prim
- PrimVertex :: Prim
- PrimEmptyGraph :: Prim
- PrimOverlay :: Prim
- PrimConnect :: Prim
- PrimInsert :: Prim
- PrimLookup :: Prim
- PrimEach :: Prim
- PrimReduce :: Prim
- PrimFilter :: Prim
- PrimJoin :: Prim
- PrimMerge :: Prim
- PrimIsPrime :: Prim
- PrimFactor :: Prim
- PrimFrac :: Prim
- PrimCrash :: Prim
- PrimUntil :: Prim
- PrimHolds :: Prim
- PrimLookupSeq :: Prim
- PrimExtendSeq :: Prim
- PrimSeed :: Prim
- PrimRandom :: Prim
- data PrimInfo = PrimInfo {
- thePrim :: Prim
- primSyntax :: String
- primExposed :: Bool
- primTable :: [PrimInfo]
- toPrim :: String -> [Prim]
- primMap :: Map Prim PrimInfo
Documentation
Primitives, i.e. built-in constants.
Constructors
PrimUOp :: UOp -> Prim | Unary operator |
PrimBOp :: BOp -> Prim | Binary operator |
PrimLeft :: Prim | Left injection into a sum type. |
PrimRight :: Prim | Right injection into a sum type. |
PrimSqrt :: Prim | Integer square root ( |
PrimFloor :: Prim | Floor of fractional type ( |
PrimCeil :: Prim | Ceiling of fractional type ( |
PrimAbs :: Prim | Absolute value ( |
PrimMin :: Prim | Min |
PrimMax :: Prim | Max |
PrimPower :: Prim | Power set (XXX or bag?) |
PrimList :: Prim | Container -> list conversion |
PrimBag :: Prim | Container -> bag conversion |
PrimSet :: Prim | Container -> set conversion |
PrimB2C :: Prim | bag -> set of counts conversion |
PrimC2B :: Prim | set of counts -> bag conversion |
PrimUC2B :: Prim | unsafe set of counts -> bag conversion that assumes all distinct |
PrimMapToSet :: Prim | Map k v -> Set (k × v) |
PrimSetToMap :: Prim | Set (k × v) -> Map k v |
PrimSummary :: Prim | Get Adjacency list of Graph |
PrimVertex :: Prim | Construct a graph Vertex |
PrimEmptyGraph :: Prim | Empty graph |
PrimOverlay :: Prim | Overlay two Graphs |
PrimConnect :: Prim | Connect Graph to another with directed edges |
PrimInsert :: Prim | Insert into map |
PrimLookup :: Prim | Get value associated with key in map |
PrimEach :: Prim | Each operation for containers |
PrimReduce :: Prim | Reduce operation for containers |
PrimFilter :: Prim | Filter operation for containers |
PrimJoin :: Prim | Monadic join for containers |
PrimMerge :: Prim | Generic merge operation for bags/sets |
PrimIsPrime :: Prim | Efficient primality test |
PrimFactor :: Prim | Factorization |
PrimFrac :: Prim | Turn a rational into a pair (num, denom) |
PrimCrash :: Prim | Crash |
PrimUntil :: Prim | [x, y, z .. e] |
PrimHolds :: Prim | Test whether a proposition holds |
PrimLookupSeq :: Prim | Lookup OEIS sequence |
PrimExtendSeq :: Prim | Extend OEIS sequence |
PrimSeed :: Prim | Generates a pseudorandom number generator |
PrimRandom :: Prim | Given a range and a generator, generates random number |
Instances
Data Prim Source # | |
Defined in Disco.Syntax.Prims Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Prim -> c Prim # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Prim # dataTypeOf :: Prim -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Prim) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Prim) # gmapT :: (forall b. Data b => b -> b) -> Prim -> Prim # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Prim -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Prim -> r # gmapQ :: (forall d. Data d => d -> u) -> Prim -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Prim -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Prim -> m Prim # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Prim -> m Prim # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Prim -> m Prim # | |
Generic Prim Source # | |
Read Prim Source # | |
Show Prim Source # | |
Eq Prim Source # | |
Ord Prim Source # | |
Alpha Prim Source # | |
Defined in Disco.Syntax.Prims Methods aeq' :: AlphaCtx -> Prim -> Prim -> Bool # fvAny' :: (Contravariant f, Applicative f) => AlphaCtx -> (AnyName -> f AnyName) -> Prim -> f Prim # close :: AlphaCtx -> NamePatFind -> Prim -> Prim # open :: AlphaCtx -> NthPatFind -> Prim -> Prim # isPat :: Prim -> DisjointSet AnyName # nthPatFind :: Prim -> NthPatFind # namePatFind :: Prim -> NamePatFind # swaps' :: AlphaCtx -> Perm AnyName -> Prim -> Prim # lfreshen' :: LFresh m => AlphaCtx -> Prim -> (Prim -> Perm AnyName -> m b) -> m b # freshen' :: Fresh m => AlphaCtx -> Prim -> m (Prim, Perm AnyName) # | |
Subst t Prim Source # | |
type Rep Prim Source # | |
Defined in Disco.Syntax.Prims type Rep Prim = D1 ('MetaData "Prim" "Disco.Syntax.Prims" "disco-0.2-Ic5OYLGQ1QL1sNsEHodldc" 'False) (((((C1 ('MetaCons "PrimUOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UOp)) :+: C1 ('MetaCons "PrimBOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BOp))) :+: (C1 ('MetaCons "PrimLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PrimRight" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimSqrt" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "PrimFloor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimCeil" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PrimAbs" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PrimMin" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimMax" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "PrimPower" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimList" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PrimBag" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PrimSet" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimB2C" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "PrimC2B" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimUC2B" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PrimMapToSet" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PrimSetToMap" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimSummary" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "PrimVertex" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimEmptyGraph" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PrimOverlay" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PrimConnect" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimInsert" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "PrimLookup" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimEach" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PrimReduce" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PrimFilter" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimJoin" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "PrimMerge" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimIsPrime" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PrimFactor" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PrimFrac" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimCrash" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "PrimUntil" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PrimHolds" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimLookupSeq" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "PrimExtendSeq" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PrimSeed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimRandom" 'PrefixI 'False) (U1 :: Type -> Type))))))) |
An info record for a single primitive name, containing the
primitive itself, its concrete syntax, and whether it is
"exposed", i.e. available to be used in the surface syntax of
the basic language. Unexposed prims can only be referenced by
enabling the Primitives language extension and prefixing their
name by $
.
Constructors
PrimInfo | |
Fields
|