Copyright | (c) Galois Inc 2015-2016 |
---|---|
License | BSD3 |
Maintainer | Rob Dockins <rdockins@galois.com> |
Stability | provisional |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Lang.Crucible.LLVM.Printf
Description
A model of C's printf
function. This does not entirely conform to the C
standard's specification of printf
; see doc/limitations.md
for the
specifics.
Synopsis
- data PrintfFlag
- data PrintfLengthModifier
- data Case
- data IntFormat
- data FloatFormat
- data PrintfConversionType
- data PrintfDirective
- parseDirectives :: [Word8] -> Either String [PrintfDirective]
- data ConversionDirective = Conversion {}
- data PrintfOperations m = PrintfOperations {
- printfGetInteger :: Int -> Bool -> PrintfLengthModifier -> m (Maybe Integer)
- printfGetFloat :: Int -> PrintfLengthModifier -> m (Maybe Rational)
- printfGetPointer :: Int -> m String
- printfGetString :: Int -> Maybe Int -> m [Word8]
- printfSetInteger :: Int -> PrintfLengthModifier -> Int -> m ()
- printfUnsupported :: !(forall a. HasCallStack => String -> m a)
- executeDirectives :: forall m. Monad m => PrintfOperations m -> [PrintfDirective] -> m (ByteString, Int)
- formatInteger :: Maybe Integer -> IntFormat -> Int -> Maybe Int -> Set PrintfFlag -> String
- formatRational :: Maybe Rational -> FloatFormat -> Int -> Maybe Int -> Set PrintfFlag -> Either String String
Documentation
data PrintfFlag Source #
Constructors
PrintfAlternateForm | |
PrintfZeroPadding | |
PrintfNegativeWidth | |
PrintfPosSpace | |
PrintfPosPlus | |
PrintfThousandsSep |
Instances
Show PrintfFlag Source # | |
Defined in Lang.Crucible.LLVM.Printf Methods showsPrec :: Int -> PrintfFlag -> ShowS # show :: PrintfFlag -> String # showList :: [PrintfFlag] -> ShowS # | |
Eq PrintfFlag Source # | |
Defined in Lang.Crucible.LLVM.Printf | |
Ord PrintfFlag Source # | |
Defined in Lang.Crucible.LLVM.Printf Methods compare :: PrintfFlag -> PrintfFlag -> Ordering # (<) :: PrintfFlag -> PrintfFlag -> Bool # (<=) :: PrintfFlag -> PrintfFlag -> Bool # (>) :: PrintfFlag -> PrintfFlag -> Bool # (>=) :: PrintfFlag -> PrintfFlag -> Bool # max :: PrintfFlag -> PrintfFlag -> PrintfFlag # min :: PrintfFlag -> PrintfFlag -> PrintfFlag # |
data PrintfLengthModifier Source #
Constructors
Len_Byte | |
Len_Short | |
Len_Long | |
Len_LongLong | |
Len_LongDouble | |
Len_IntMax | |
Len_PtrDiff | |
Len_Sizet | |
Len_NoMod |
Instances
Show PrintfLengthModifier Source # | |
Defined in Lang.Crucible.LLVM.Printf Methods showsPrec :: Int -> PrintfLengthModifier -> ShowS # show :: PrintfLengthModifier -> String # showList :: [PrintfLengthModifier] -> ShowS # | |
Eq PrintfLengthModifier Source # | |
Defined in Lang.Crucible.LLVM.Printf Methods (==) :: PrintfLengthModifier -> PrintfLengthModifier -> Bool # (/=) :: PrintfLengthModifier -> PrintfLengthModifier -> Bool # | |
Ord PrintfLengthModifier Source # | |
Defined in Lang.Crucible.LLVM.Printf Methods compare :: PrintfLengthModifier -> PrintfLengthModifier -> Ordering # (<) :: PrintfLengthModifier -> PrintfLengthModifier -> Bool # (<=) :: PrintfLengthModifier -> PrintfLengthModifier -> Bool # (>) :: PrintfLengthModifier -> PrintfLengthModifier -> Bool # (>=) :: PrintfLengthModifier -> PrintfLengthModifier -> Bool # max :: PrintfLengthModifier -> PrintfLengthModifier -> PrintfLengthModifier # min :: PrintfLengthModifier -> PrintfLengthModifier -> PrintfLengthModifier # |
Instances
Show IntFormat Source # | |
Eq IntFormat Source # | |
Ord IntFormat Source # | |
data FloatFormat Source #
Constructors
FloatFormat_Scientific Case | |
FloatFormat_Standard Case | |
FloatFormat_Auto Case | |
FloatFormat_Hex Case |
Instances
Show FloatFormat Source # | |
Defined in Lang.Crucible.LLVM.Printf Methods showsPrec :: Int -> FloatFormat -> ShowS # show :: FloatFormat -> String # showList :: [FloatFormat] -> ShowS # | |
Eq FloatFormat Source # | |
Defined in Lang.Crucible.LLVM.Printf | |
Ord FloatFormat Source # | |
Defined in Lang.Crucible.LLVM.Printf Methods compare :: FloatFormat -> FloatFormat -> Ordering # (<) :: FloatFormat -> FloatFormat -> Bool # (<=) :: FloatFormat -> FloatFormat -> Bool # (>) :: FloatFormat -> FloatFormat -> Bool # (>=) :: FloatFormat -> FloatFormat -> Bool # max :: FloatFormat -> FloatFormat -> FloatFormat # min :: FloatFormat -> FloatFormat -> FloatFormat # |
data PrintfConversionType Source #
Constructors
Conversion_Integer IntFormat | |
Conversion_Floating FloatFormat | |
Conversion_Char | |
Conversion_String | |
Conversion_Pointer | |
Conversion_CountChars |
Instances
Show PrintfConversionType Source # | |
Defined in Lang.Crucible.LLVM.Printf Methods showsPrec :: Int -> PrintfConversionType -> ShowS # show :: PrintfConversionType -> String # showList :: [PrintfConversionType] -> ShowS # | |
Eq PrintfConversionType Source # | |
Defined in Lang.Crucible.LLVM.Printf Methods (==) :: PrintfConversionType -> PrintfConversionType -> Bool # (/=) :: PrintfConversionType -> PrintfConversionType -> Bool # | |
Ord PrintfConversionType Source # | |
Defined in Lang.Crucible.LLVM.Printf Methods compare :: PrintfConversionType -> PrintfConversionType -> Ordering # (<) :: PrintfConversionType -> PrintfConversionType -> Bool # (<=) :: PrintfConversionType -> PrintfConversionType -> Bool # (>) :: PrintfConversionType -> PrintfConversionType -> Bool # (>=) :: PrintfConversionType -> PrintfConversionType -> Bool # max :: PrintfConversionType -> PrintfConversionType -> PrintfConversionType # min :: PrintfConversionType -> PrintfConversionType -> PrintfConversionType # |
data PrintfDirective Source #
Instances
Show PrintfDirective Source # | |
Defined in Lang.Crucible.LLVM.Printf Methods showsPrec :: Int -> PrintfDirective -> ShowS # show :: PrintfDirective -> String # showList :: [PrintfDirective] -> ShowS # | |
Eq PrintfDirective Source # | |
Defined in Lang.Crucible.LLVM.Printf Methods (==) :: PrintfDirective -> PrintfDirective -> Bool # (/=) :: PrintfDirective -> PrintfDirective -> Bool # | |
Ord PrintfDirective Source # | |
Defined in Lang.Crucible.LLVM.Printf Methods compare :: PrintfDirective -> PrintfDirective -> Ordering # (<) :: PrintfDirective -> PrintfDirective -> Bool # (<=) :: PrintfDirective -> PrintfDirective -> Bool # (>) :: PrintfDirective -> PrintfDirective -> Bool # (>=) :: PrintfDirective -> PrintfDirective -> Bool # max :: PrintfDirective -> PrintfDirective -> PrintfDirective # min :: PrintfDirective -> PrintfDirective -> PrintfDirective # |
parseDirectives :: [Word8] -> Either String [PrintfDirective] Source #
data ConversionDirective Source #
Constructors
Conversion | |
Instances
Show ConversionDirective Source # | |
Defined in Lang.Crucible.LLVM.Printf Methods showsPrec :: Int -> ConversionDirective -> ShowS # show :: ConversionDirective -> String # showList :: [ConversionDirective] -> ShowS # | |
Eq ConversionDirective Source # | |
Defined in Lang.Crucible.LLVM.Printf Methods (==) :: ConversionDirective -> ConversionDirective -> Bool # (/=) :: ConversionDirective -> ConversionDirective -> Bool # | |
Ord ConversionDirective Source # | |
Defined in Lang.Crucible.LLVM.Printf Methods compare :: ConversionDirective -> ConversionDirective -> Ordering # (<) :: ConversionDirective -> ConversionDirective -> Bool # (<=) :: ConversionDirective -> ConversionDirective -> Bool # (>) :: ConversionDirective -> ConversionDirective -> Bool # (>=) :: ConversionDirective -> ConversionDirective -> Bool # max :: ConversionDirective -> ConversionDirective -> ConversionDirective # min :: ConversionDirective -> ConversionDirective -> ConversionDirective # |
data PrintfOperations m Source #
Constructors
PrintfOperations | |
Fields
|
executeDirectives :: forall m. Monad m => PrintfOperations m -> [PrintfDirective] -> m (ByteString, Int) Source #
Given a list of PrintfDirective
s, compute the resulting ByteString
and its length.
We make an effort not to assume a particular text encoding for the
ByteString
that this returns. Some parts of the implementation do use
functionality from Data.ByteString.Char8, which is limited to the subset
of Unicode covered by code points 0-255. We believe these uses are justified,
however, and we have left comments explaining the reasoning behind each use.
formatInteger :: Maybe Integer -> IntFormat -> Int -> Maybe Int -> Set PrintfFlag -> String Source #