Copyright | Galois, Inc. 2010-2014 |
---|---|
License | BSD3 |
Maintainer | jhendrix@galois.com |
Stability | experimental |
Portability | non-portable (c2hs, language extensions) |
Safe Haskell | None |
Language | Haskell98 |
Bindings to aig/gia/gia.h
for manipulating and
running algorithms on scalable and-inverter graphs (GIA), a
representation that is optimized for memory-efficiency. These
functions power the next-generation of ABC algorithms that have
not been officially released yet, and can be identified by the
prefix of an ampersand, as in &cec
, in the interactive ABC
interface.
- type Gia_Man_t = Ptr Gia_Man_t_
- data Gia_Man_t_
- giaManNObjs :: Field Gia_Man_t CInt
- giaManFanData :: Gia_Man_t -> IO (Ptr CInt)
- type Gia_Obj_t = Ptr Gia_Obj_t_
- getGiaObjValue :: Gia_Obj_t -> IO CUInt
- setGiaObjValue :: Gia_Obj_t -> CUInt -> IO ()
- newtype GiaVar = GiaVar {}
- newtype GiaLit = GiaLit {}
- giaManConst0Lit :: GiaLit
- giaManConst1Lit :: GiaLit
- giaLitIsCompl :: GiaLit -> Bool
- giaLitVar :: GiaLit -> GiaVar
- giaVarLit :: GiaVar -> GiaLit
- giaLitNotCond :: GiaLit -> Bool -> GiaLit
- giaManCexComb :: Gia_Man_t -> IO Abc_Cex_t
- giaManConst0 :: Gia_Man_t -> IO Gia_Obj_t
- giaManCis :: Gia_Man_t -> IO Vec_Int_t
- giaManCos :: Gia_Man_t -> IO Vec_Int_t
- giaManCiNum :: Gia_Man_t -> IO CInt
- giaManCoNum :: Gia_Man_t -> IO CInt
- giaManPiNum :: Gia_Man_t -> IO CInt
- giaManPoNum :: Gia_Man_t -> IO CInt
- giaManAndNum :: Gia_Man_t -> IO CInt
- getGiaManRegNum :: Gia_Man_t -> IO CInt
- setGiaManRegNum :: Gia_Man_t -> CInt -> IO ()
- giaManCiVar :: Gia_Man_t -> CInt -> IO GiaVar
- giaManCoVar :: Gia_Man_t -> CInt -> IO GiaVar
- giaManCi :: Gia_Man_t -> CInt -> IO Gia_Obj_t
- giaManCo :: Gia_Man_t -> CInt -> IO Gia_Obj_t
- giaManObj :: Gia_Man_t -> GiaVar -> IO Gia_Obj_t
- gia_none :: CUInt
- giaObjIsCo :: Gia_Obj_t -> IO Bool
- giaObjDiff0 :: Gia_Obj_t -> IO CUInt
- giaObjDiff1 :: Gia_Obj_t -> IO CUInt
- giaObjFaninC0 :: Gia_Obj_t -> IO Bool
- giaObjFaninC1 :: Gia_Obj_t -> IO Bool
- giaObjMark0 :: Gia_Obj_t -> IO Bool
- giaObjMark1 :: Gia_Obj_t -> IO Bool
- giaObjChild0 :: Gia_Obj_t -> IO Gia_Obj_t
- giaObjChild1 :: Gia_Obj_t -> IO Gia_Obj_t
- giaObjFaninId0 :: Gia_Obj_t -> GiaVar -> IO GiaVar
- giaObjFaninId1 :: Gia_Obj_t -> GiaVar -> IO GiaVar
- giaObjIsTerm :: Gia_Obj_t -> IO Bool
- giaObjIsAndOrConst0 :: Gia_Obj_t -> IO Bool
- giaObjId :: Gia_Man_t -> Gia_Obj_t -> IO GiaVar
- giaManObjNum :: Gia_Man_t -> IO CInt
- giaLitNot :: GiaLit -> GiaLit
- giaRegular :: Gia_Obj_t -> Gia_Obj_t
- giaIsComplement :: Gia_Obj_t -> Bool
- giaObjToLit :: Gia_Man_t -> Gia_Obj_t -> IO GiaLit
- giaObjFromLit :: Gia_Man_t -> GiaLit -> IO Gia_Obj_t
- giaManForEachObj1_ :: Gia_Man_t -> (Gia_Obj_t -> GiaVar -> IO b) -> IO ()
- giaManForEachCo :: Gia_Man_t -> (Gia_Obj_t -> Int -> IO b) -> IO [b]
- giaManAppendCi :: Gia_Man_t -> IO GiaLit
- giaManAppendCo :: Gia_Man_t -> GiaLit -> IO GiaLit
- giaManAppendAnd :: Gia_Man_t -> GiaLit -> GiaLit -> IO GiaLit
- giaAigerRead :: String -> Bool -> Bool -> IO Gia_Man_t
- giaAigerWrite :: Gia_Man_t -> String -> Bool -> Bool -> IO ()
- giaManMiter :: Gia_Man_t -> Gia_Man_t -> Int -> Bool -> Bool -> Bool -> Bool -> IO Gia_Man_t
- giaDupLit :: Gia_Man_t -> Gia_Man_t -> GiaLit -> IO GiaLit
- giaManDupNormalize :: Gia_Man_t -> IO Gia_Man_t
- giaManHashAlloc :: Gia_Man_t -> IO ()
- giaManHashStart :: Gia_Man_t -> IO ()
- giaManHashStop :: Gia_Man_t -> IO ()
- giaManHashAnd :: Gia_Man_t -> GiaLit -> GiaLit -> IO GiaLit
- giaManHashXor :: Gia_Man_t -> GiaLit -> GiaLit -> IO GiaLit
- giaManHashMux :: Gia_Man_t -> GiaLit -> GiaLit -> GiaLit -> IO GiaLit
- giaManStart :: CInt -> IO Gia_Man_t
- giaManStop :: Gia_Man_t -> IO ()
- p_giaManStop :: FunPtr (Gia_Man_t -> IO ())
- giaManCleanup :: Gia_Man_t -> IO Gia_Man_t
- giaManFillValue :: Gia_Man_t -> IO ()
- clearGiaObj :: Gia_Obj_t -> IO ()
Documentation
type Gia_Man_t = Ptr Gia_Man_t_ Source
data Gia_Man_t_ Source
type Gia_Obj_t = Ptr Gia_Obj_t_ Source
A pointer to a GIA object. GIA objects are pointers to structs in ABC, and represent literals in the AIG. The low-order bit of the pointer is set to 1 if the literal has been complemented, and so care must be taken to only dereference positive pointers. The object is also a bitfield, so care must be taken when accessing fields.
Pointers to GIA objects may be invalidated when adding a new object.
getGiaObjValue :: Gia_Obj_t -> IO CUInt Source
setGiaObjValue :: Gia_Obj_t -> CUInt -> IO () Source
Also known as the node's id. No complement info.
Literals store complement information.
giaLitIsCompl :: GiaLit -> Bool Source
giaLitNotCond :: GiaLit -> Bool -> GiaLit Source
Memory management
Base
Network getters
giaManCexComb :: Gia_Man_t -> IO Abc_Cex_t Source
giaManConst0 :: Gia_Man_t -> IO Gia_Obj_t Source
giaManCiNum :: Gia_Man_t -> IO CInt Source
giaManCoNum :: Gia_Man_t -> IO CInt Source
giaManPiNum :: Gia_Man_t -> IO CInt Source
giaManPoNum :: Gia_Man_t -> IO CInt Source
giaManAndNum :: Gia_Man_t -> IO CInt Source
getGiaManRegNum :: Gia_Man_t -> IO CInt Source
setGiaManRegNum :: Gia_Man_t -> CInt -> IO () Source
giaManCiVar :: Gia_Man_t -> CInt -> IO GiaVar Source
Get var index of combinational input at given index.
giaObjIsCo :: Gia_Obj_t -> IO Bool Source
Returns true if this is a combinational output (latch or primary output).
giaObjDiff0 :: Gia_Obj_t -> IO CUInt Source
Returns iDiff0 field of object Note: iDiff0 is a bitfield, so this may be more likely to break on unexpected compilers.
giaObjDiff1 :: Gia_Obj_t -> IO CUInt Source
Returns iDiff1 field of object Note: iDiff1 is a bitfield, so this may be more likely to break on unexpected compilers.
giaObjFaninC0 :: Gia_Obj_t -> IO Bool Source
Get the complement attribute of first fanin
giaObjFaninC1 :: Gia_Obj_t -> IO Bool Source
giaObjMark0 :: Gia_Obj_t -> IO Bool Source
Get first user defined mark
giaObjMark1 :: Gia_Obj_t -> IO Bool Source
Get second user defined mark
giaObjChild0 :: Gia_Obj_t -> IO Gia_Obj_t Source
giaObjChild1 :: Gia_Obj_t -> IO Gia_Obj_t Source
giaObjIsTerm :: Gia_Obj_t -> IO Bool Source
giaObjIsAndOrConst0 :: Gia_Obj_t -> IO Bool Source
giaObjId :: Gia_Man_t -> Gia_Obj_t -> IO GiaVar Source
Returns the variable index associated with the object.
giaManObjNum :: Gia_Man_t -> IO CInt Source
Handling literals
giaRegular :: Gia_Obj_t -> Gia_Obj_t Source
Remove negation.
giaIsComplement :: Gia_Obj_t -> Bool Source
Iterators
Construction
giaManAppendCi :: Gia_Man_t -> IO GiaLit Source
giaManAppendAnd :: Gia_Man_t -> GiaLit -> GiaLit -> IO GiaLit Source
This directly appends the literal to the GIA bypassing any hash-consing.
Functions
giaAiger.c
giaDup.c
giaDupLit :: Gia_Man_t -> Gia_Man_t -> GiaLit -> IO GiaLit Source
giaManDupDfsLazyLit pNew p l
copies a lit l
in p
to pNew
and returns the lit in pNew
.
giaHash.c
giaManHashAlloc :: Gia_Man_t -> IO () Source
giaManHashStart :: Gia_Man_t -> IO () Source
giaManHashStop :: Gia_Man_t -> IO () Source
giaMan.c
giaManStart :: CInt -> IO Gia_Man_t Source
giaManStop :: Gia_Man_t -> IO () Source
p_giaManStop :: FunPtr (Gia_Man_t -> IO ()) Source
giaManCleanup :: Gia_Man_t -> IO Gia_Man_t Source
giaManFillValue :: Gia_Man_t -> IO () Source
misc
clearGiaObj :: Gia_Obj_t -> IO () Source