| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Circus.Types
Synopsis
- newtype Schema = Schema {}
- data Module = Module {}
- newtype ModuleName = ModuleName {}
- newtype PortName = PortName {
- getPortName :: Text
- newtype CellName = CellName {
- getCellName :: Text
- data Port = Port {
- portDirection :: Direction
- portBits :: [Bit]
- newtype Bit = Bit {}
- data Cell = Cell {}
- data Parameter
- data Direction
- data CellType = CellGeneric Text
- pattern CellMux :: CellType
- pattern CellMuxBus :: CellType
- pattern CellTribuf :: CellType
- pattern CellAnd :: CellType
- pattern CellOr :: CellType
- pattern CellNand :: CellType
- pattern CellNor :: CellType
- pattern CellXor :: CellType
- pattern CellXnor :: CellType
- pattern CellNot :: CellType
- pattern CellAdd :: CellType
- pattern CellEq :: CellType
- pattern CellDff :: CellType
- pattern CellDffn :: CellType
- pattern CellLt :: CellType
- pattern CellGe :: CellType
- pattern CellConstant :: CellType
- renderModuleBS :: Module -> ByteString
- renderModuleString :: Module -> String
- mkCell :: CellType -> Map PortName (Direction, [Bit]) -> Cell
- mkCell' :: CellType -> Map Text Value -> Map PortName (Direction, [Bit]) -> Cell
Documentation
A collection of modules.
Constructors
| Schema | |
Fields | |
Instances
| Eq Schema Source # | |
| Data Schema Source # | |
Defined in Circus.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Schema -> c Schema # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Schema # toConstr :: Schema -> Constr # dataTypeOf :: Schema -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Schema) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Schema) # gmapT :: (forall b. Data b => b -> b) -> Schema -> Schema # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Schema -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Schema -> r # gmapQ :: (forall d. Data d => d -> u) -> Schema -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Schema -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Schema -> m Schema # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Schema -> m Schema # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Schema -> m Schema # | |
| Show Schema Source # | |
| Semigroup Schema Source # | |
| Monoid Schema Source # | |
| ToJSON Schema Source # | |
Defined in Circus.Types | |
| FromJSON Schema Source # | |
Constructors
| Module | |
Fields
| |
Instances
| Eq Module Source # | |
| Data Module Source # | |
Defined in Circus.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Module -> c Module # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Module # toConstr :: Module -> Constr # dataTypeOf :: Module -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Module) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Module) # gmapT :: (forall b. Data b => b -> b) -> Module -> Module # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r # gmapQ :: (forall d. Data d => d -> u) -> Module -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Module -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Module -> m Module # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module # | |
| Show Module Source # | |
| Semigroup Module Source # | |
| Monoid Module Source # | |
| ToJSON Module Source # | |
Defined in Circus.Types | |
| FromJSON Module Source # | |
newtype ModuleName Source #
Constructors
| ModuleName | |
Fields | |
Instances
Constructors
| PortName | |
Fields
| |
Instances
| Eq PortName Source # | |
| Data PortName Source # | |
Defined in Circus.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PortName -> c PortName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PortName # toConstr :: PortName -> Constr # dataTypeOf :: PortName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PortName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PortName) # gmapT :: (forall b. Data b => b -> b) -> PortName -> PortName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PortName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PortName -> r # gmapQ :: (forall d. Data d => d -> u) -> PortName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PortName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PortName -> m PortName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PortName -> m PortName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PortName -> m PortName # | |
| Ord PortName Source # | |
Defined in Circus.Types | |
| Show PortName Source # | |
| IsString PortName Source # | |
Defined in Circus.Types Methods fromString :: String -> PortName # | |
| ToJSON PortName Source # | |
Defined in Circus.Types | |
| ToJSONKey PortName Source # | |
Defined in Circus.Types | |
| FromJSON PortName Source # | |
| FromJSONKey PortName Source # | |
Defined in Circus.Types Methods | |
Constructors
| CellName | |
Fields
| |
Instances
| Eq CellName Source # | |
| Data CellName Source # | |
Defined in Circus.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CellName -> c CellName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CellName # toConstr :: CellName -> Constr # dataTypeOf :: CellName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CellName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CellName) # gmapT :: (forall b. Data b => b -> b) -> CellName -> CellName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CellName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CellName -> r # gmapQ :: (forall d. Data d => d -> u) -> CellName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CellName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CellName -> m CellName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CellName -> m CellName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CellName -> m CellName # | |
| Ord CellName Source # | |
Defined in Circus.Types | |
| Show CellName Source # | |
| IsString CellName Source # | |
Defined in Circus.Types Methods fromString :: String -> CellName # | |
| ToJSON CellName Source # | |
Defined in Circus.Types | |
| ToJSONKey CellName Source # | |
Defined in Circus.Types | |
| FromJSON CellName Source # | |
| FromJSONKey CellName Source # | |
Defined in Circus.Types Methods | |
Constructors
| Port | |
Fields
| |
Instances
| Eq Port Source # | |
| Data Port Source # | |
Defined in Circus.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Port -> c Port # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Port # dataTypeOf :: Port -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Port) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Port) # gmapT :: (forall b. Data b => b -> b) -> Port -> Port # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Port -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Port -> r # gmapQ :: (forall d. Data d => d -> u) -> Port -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Port -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Port -> m Port # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Port -> m Port # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Port -> m Port # | |
| Show Port Source # | |
| ToJSON Port Source # | |
Defined in Circus.Types | |
| FromJSON Port Source # | |
A single wire. Bits are defined implicitly by a unique ID. Every component that references the bit will be connected with a common node.
Instances
| Eq Bit Source # | |
| Data Bit Source # | |
Defined in Circus.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bit -> c Bit # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bit # dataTypeOf :: Bit -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bit) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bit) # gmapT :: (forall b. Data b => b -> b) -> Bit -> Bit # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bit -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bit -> r # gmapQ :: (forall d. Data d => d -> u) -> Bit -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Bit -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bit -> m Bit # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bit -> m Bit # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bit -> m Bit # | |
| Num Bit Source # | |
| Ord Bit Source # | |
| Show Bit Source # | |
| ToJSON Bit Source # | |
Defined in Circus.Types | |
| FromJSON Bit Source # | |
Constructors
| Cell | |
Fields
| |
Instances
| Eq Cell Source # | |
| Data Cell Source # | |
Defined in Circus.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cell -> c Cell # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Cell # dataTypeOf :: Cell -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Cell) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cell) # gmapT :: (forall b. Data b => b -> b) -> Cell -> Cell # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r # gmapQ :: (forall d. Data d => d -> u) -> Cell -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Cell -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Cell -> m Cell # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Cell -> m Cell # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Cell -> m Cell # | |
| Show Cell Source # | |
| ToJSON Cell Source # | |
Defined in Circus.Types | |
| FromJSON Cell Source # | |
Constructors
| Width PortName | How many bits wide is the given |
| Signed PortName | Is the given |
Instances
| Eq Parameter Source # | |
| Data Parameter Source # | |
Defined in Circus.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Parameter -> c Parameter # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Parameter # toConstr :: Parameter -> Constr # dataTypeOf :: Parameter -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Parameter) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Parameter) # gmapT :: (forall b. Data b => b -> b) -> Parameter -> Parameter # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Parameter -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Parameter -> r # gmapQ :: (forall d. Data d => d -> u) -> Parameter -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Parameter -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Parameter -> m Parameter # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Parameter -> m Parameter # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Parameter -> m Parameter # | |
| Ord Parameter Source # | |
| Show Parameter Source # | |
| Generic Parameter Source # | |
| ToJSON Parameter Source # | |
Defined in Circus.Types | |
| ToJSONKey Parameter Source # | |
Defined in Circus.Types | |
| FromJSON Parameter Source # | |
| FromJSONKey Parameter Source # | |
Defined in Circus.Types Methods | |
| type Rep Parameter Source # | |
Defined in Circus.Types type Rep Parameter = D1 ('MetaData "Parameter" "Circus.Types" "circus-0.1.0.0-7gwvoNsbnBR3ebwlAtgx3C" 'False) (C1 ('MetaCons "Width" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PortName)) :+: C1 ('MetaCons "Signed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PortName))) | |
Instances
Master list of cells, and their associated names is available here:
https://raw.githubusercontent.com/nturley/netlistsvg/master/lib/default.svg?sanitize=true
Constructors
| CellGeneric Text |
Instances
| Eq CellType Source # | |
| Data CellType Source # | |
Defined in Circus.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CellType -> c CellType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CellType # toConstr :: CellType -> Constr # dataTypeOf :: CellType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CellType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CellType) # gmapT :: (forall b. Data b => b -> b) -> CellType -> CellType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CellType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CellType -> r # gmapQ :: (forall d. Data d => d -> u) -> CellType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CellType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CellType -> m CellType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CellType -> m CellType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CellType -> m CellType # | |
| Ord CellType Source # | |
Defined in Circus.Types | |
| Show CellType Source # | |
| ToJSON CellType Source # | |
Defined in Circus.Types | |
| FromJSON CellType Source # | |
pattern CellMuxBus :: CellType Source #
pattern CellTribuf :: CellType Source #
pattern CellConstant :: CellType Source #
renderModuleBS :: Module -> ByteString Source #
renderModuleString :: Module -> String Source #