apple-0.3.0.0: Apple array language compiler
Safe HaskellSafe-Inferred
LanguageHaskell2010

Asm.M

Documentation

data CFunc Source #

Constructors

Malloc 
Free 
JR 
DR 
Exp 
Log 
Pow 

Instances

Instances details
NFData CFunc Source # 
Instance details

Defined in Asm.M

Methods

rnf :: CFunc -> () #

Generic CFunc Source # 
Instance details

Defined in Asm.M

Associated Types

type Rep CFunc 
Instance details

Defined in Asm.M

type Rep CFunc = D1 ('MetaData "CFunc" "Asm.M" "apple-0.3.0.0-inplace" 'False) ((C1 ('MetaCons "Malloc" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Free" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "JR" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Exp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Log" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pow" 'PrefixI 'False) (U1 :: Type -> Type))))

Methods

from :: CFunc -> Rep CFunc x #

to :: Rep CFunc x -> CFunc #

Pretty CFunc Source # 
Instance details

Defined in Asm.M

Methods

pretty :: CFunc -> Doc ann #

prettyList :: [CFunc] -> Doc ann #

type Rep CFunc Source # 
Instance details

Defined in Asm.M

type Rep CFunc = D1 ('MetaData "CFunc" "Asm.M" "apple-0.3.0.0-inplace" 'False) ((C1 ('MetaCons "Malloc" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Free" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "JR" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Exp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Log" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pow" 'PrefixI 'False) (U1 :: Type -> Type))))

foldMapA :: (Applicative f, Traversable t, Monoid m) => (a -> f m) -> t a -> f m Source #

i4 :: Doc ann -> Doc ann Source #

pAsm :: Pretty isn => [isn] -> Doc ann Source #

prettyAsm :: Pretty isn => (AsmData, [isn]) -> Doc ann Source #

mFree :: Maybe (Ptr a) -> IO () Source #