[Pkg-haskell-commits] [SCM] haskell-testpack branch, master, updated. debian/1.0.2-1-4-gb0d6b36

John Goerzen jgoerzen at complete.org
Fri Apr 23 15:12:14 UTC 2010


The following commit has been merged in the master branch:
commit 6596063af2f814f0194bc829450da3a9ce5700ff
Author: John Goerzen <jgoerzen at complete.org>
Date:   Fri Oct 20 00:53:51 2006 +0100

    Remove MissingH.Printf
    
    Everyone should now be using the standard Text.Printf

diff --git a/MissingH.cabal b/MissingH.cabal
index 554d396..13977de 100644
--- a/MissingH.cabal
+++ b/MissingH.cabal
@@ -36,7 +36,6 @@ Exposed-Modules: MissingH.Str, MissingH.IO, MissingH.IO.Binary, MissingH.List,
     MissingH.ConfigParser.Types,
     MissingH.ConfigParser.Parser,
     MissingH.ConfigParser.Lexer,
-  MissingH.Printf, MissingH.Printf.Types, MissingH.Printf.Printer,
   MissingH.Bits,
   MissingH.Checksum.CRC32.Posix, MissingH.Checksum.CRC32.GZip,
    MissingH.Checksum.MD5, MissingH.Checksum.MD5.Zord64_HARD,
diff --git a/MissingH/Printf.hs b/MissingH/Printf.hs
deleted file mode 100644
index e9f402d..0000000
--- a/MissingH/Printf.hs
+++ /dev/null
@@ -1,501 +0,0 @@
-{- arch-tag: Printf utilities main file
-Copyright (C) 2004 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-{- |
-   Module     : MissingH.Printf
-   Copyright  : Copyright (C) 2004 John Goerzen
-   License    : GNU GPL, version 2 or above
-
-   Maintainer : John Goerzen <jgoerzen at complete.org> 
-   Stability  : provisional
-   Portability: portable
-
-This module provides various helpful utilities for using a C-style printf().
-
-Copyright (c) 2004 John Goerzen, jgoerzen\@complete.org
-
-Some code in sub-modules written by Ian Lynagh
-
-Inspiration and ideas from haskell-xml-rpc by Bjorn Bringert
-
-Please scroll down to read the detailed documentation.
-
-/NOTE/: to use this module under ghc, you must use:
-
-> -fallow-overlapping-instances
-
-With hugs:
-
-> -98 +o
-
--}
-
-module MissingH.Printf
-    {-# DEPRECATED "Please use the standard Text.Printf instead" #-}
-                      (-- * Introduction
-                       -- $introduction
-
-                       -- * Methods of Use
-                       -- $methodsofuse
-
-                       -- ** Variable-Argument Ouptut
-                       vsprintf,
-                       vprintf,
-                       vfprintf,
-                       -- *** Casting Notes
-                       -- $castingnotes
-                       ps, pio,
-
-                       -- ** List-Argument Output
-                       sprintf,
-                       printf,
-                       fprintf,
-
-                       -- ** Mapping Output Types
-                       -- $mappingoutput
-
-                       -- *** Association List Output
-                       sprintfAL, printfAL, fprintfAL,
-
-                       -- *** FiniteMap Output
-                       sprintfFM, printfFM, fprintfFM,
-
-                       -- *** Generic\/Custom Output
-                       sprintfG, printfG, fprintfG,
-
-                       -- * Utility Function
-                       v,
-                       -- * Differences from C
-                       -- $differencesfromc
-
-                       -- * Important Haskell Notes
-                       -- $haskellnotes
-
-                       -- * Full Example Programs
-                       -- $fullexamples
-
-                       -- * Underlying Types
-                       Value(..),
-                       PFType(..)
-                       ) where
-
-import MissingH.Str
-import Data.List
-import System.IO
-import MissingH.Printf.Types
-import MissingH.Printf.Printer(get_conversion_func, fix_width)
-import Text.Regex
-import Data.FiniteMap(lookupFM, FiniteMap)
-
-v :: PFType a => a -> Value
-v = toValue
-
-sprintfre = mkRegex "^([#0 +'O-]*)([0-9]*)(\\.[0-9]*)?(.)"
-
-toflags :: String -> [Flag]
-toflags "" = []
-toflags (x:xs) = (case x of
-                      '#' -> AlternateForm
-                      '0' -> ZeroPadded
-                      '-' -> LeftAdjust
-                      ' ' -> BlankPlus
-                      '+' -> Plus
-                      '\'' -> Thousands
-                      'I' -> AlternativeDigits) : toflags xs
-
-mkflags :: String -> [Flag]
-mkflags x =
-    let flags = toflags x
-        flags' = if LeftAdjust `elem` flags then filter (/= ZeroPadded) flags
-                                            else flags
-        flags'' = if Plus `elem` flags then filter (/= BlankPlus) flags
-                                       else flags'
-        in
-        flags''
-
-normLookup :: String -> [Value] -> (String, String, [Value])
-normLookup xs (y : ys) =
-    case matchRegexAll sprintfre xs of
-         Nothing -> error $ "Problem in format string at %" ++ xs
-         --Just (_, _, r, x) -> "<" ++ show x ++ ">" ++ sprintf r ys
-         Just (_, _, remainder, [flagstr, widthstr, precstr, [fmt]]) ->
-             let width = if widthstr == "" then Nothing else Just ((read widthstr)::Width)
-                 prec = if precstr == "" 
-                        then Nothing 
-                        else Just (if length precstr >= 1
-                                   then abs $ read (drop 1 precstr)
-                                   else 0)
-                 flags = mkflags flagstr
-                 in
-                 --(show width) ++ sprintf remainder ys
-                 (fix_width flags width ((get_conversion_func fmt y flags width prec)), remainder, ys)
-         _ -> error $ "Problem matching format string at %" ++ xs
-
-alre = mkRegex "^\\(([^)]+)\\)"
-gLookup :: (String -> a -> Maybe Value) -> String -> a -> (String, String)
-gLookup lookupfunc xs y =
-    case matchRegexAll alre xs of
-         Nothing -> error $ "No varname in keyed lookup at %" ++ xs
-         Just (_, _, remainder, [varname]) ->
-             let val = case lookupfunc varname y of
-                               Just z -> z
-                               Nothing -> error $ 
-                                          "Failed to find key " ++ varname ++
-                                          " in keyed lookup table"
-                 in
-                 case normLookup remainder [val] of
-                      (a, b, _) -> (a, b)
-         _ -> error $ "Problem finding key in lookup at %" ++ xs
-
-{- | List version of 'vsprintf'. -}
-sprintf :: String -> [Value] -> String
-sprintf [] [] = []
-sprintf ('%' : '%' : xs) y = '%' : sprintf xs y
-sprintf ('%' : xs) y =
-    let (this, remainder, ys) = normLookup xs y
-        in
-        this ++ sprintf remainder ys
-sprintf (x:xs) y = x : sprintf xs y
-
-{- | Generic version of 'sprintf'.
-
-This is one of the map-style functions and provides a way for you to integrate
-your own lookup support into sprintf.  The first parameter is a lookup
-function.  It takes a variable name and a map data object and returns
-a sought-after 'Value'.  It is expected to return Nothing if the given
-key could not be found.
-
-You might be interested to know that related helper functions can be defined
-thusly:
-
->sprintfAL = sprintfG lookup
->sprintfFM = sprintfG (flip lookupFM)
--}
-sprintfG :: (String -> a -> Maybe Value)-- ^ Lookup function
-         -> String                      -- ^ Format string
-         ->  a                          -- ^ Lookup data
-         -> String                      -- ^ Return value
-sprintfG _ [] _ = []
-sprintfG conv ('%' : '%' : xs) y = '%' : sprintfG conv xs y
-sprintfG conv ('%' : xs) y =
-    let (this, remainder) = (gLookup conv) xs y
-        in
-        this ++ sprintfG conv remainder y
-sprintfG conv (x:xs) y = x : sprintfG conv xs y
-
-{- | Association list version of 'sprintf'. -}
-sprintfAL :: String -> [(String, Value)] -> String
-sprintfAL = sprintfG lookup
-
-{- | Finite map version of 'sprintf'. -}
-sprintfFM :: String -> FiniteMap String Value -> String
-sprintfFM = sprintfG (flip lookupFM)
-
-{- | Given a format string and zero or more arguments, return a string
-that has formatted them appropriately.  This is the variable argument version
-of 'sprintf'. -}
-vsprintf :: (PFRun a) => String -> a
-vsprintf f = pfrun $ sprintf f
-
-{- | Like 'sprintf', but instead of returning a string, directs output
-to the given Handle. -}
-fprintf :: Handle -> String -> [Value] -> IO ()
-fprintf h f v = hPutStr h $ sprintf f v
-
-{- | Like 'sprintfAL', but instead of returning a string, directs output
-to the given Handle. -}
-fprintfAL :: Handle -> String -> [(String, Value)] -> IO ()
-fprintfAL h f v = hPutStr h $ sprintfAL f v
-
-{- | Like 'sprintfFM', but instead of returning a string, directs output
-to the given Handle. -}
-fprintfFM :: Handle -> String -> FiniteMap String Value -> IO ()
-fprintfFM h f v = hPutStr h $ sprintfFM f v
-
-{- | Like 'sprintfG', but instead of returning a string, directs output
-to the given Handle. -}
-fprintfG :: Handle -> (String -> a -> Maybe Value) -> String -> a -> IO ()
-fprintfG h c f v = hPutStr h $ sprintfG c f v
-
-{- | Like 'fprintf', but directs output to standard out instead of
-taking an explicit Handle. -}
-printf :: String -> [Value] -> IO ()
-printf f v = fprintf stdout f v
-
-{- | Like 'fprintfAL', but directs output to standard out instead of
-taking an explicit Handle. -}
-printfAL :: String -> [(String, Value)] -> IO ()
-printfAL = fprintfAL stdout
-
-{- | Like 'fprintfFM', but directs output to standard out instead of
-taking an explicit Handle. -}
-printfFM :: String -> FiniteMap String Value -> IO ()
-printfFM = fprintfFM stdout
-
-{- | Like 'fprintfG', but directs output to standard out instead of
-taking an explicit Handle. -}
-printfG :: (String -> a -> Maybe Value) -> String -> a -> IO ()
-printfG = fprintfG stdout
-
-{- | Like 'vsprintf', but instead of returning a string, directs output to
-the given Handle. -}
-vfprintf :: IOPFRun a => Handle -> String -> a
-vfprintf h f = iopfrun h $ sprintf f
-
-{- | Like 'vfprintf', but directs output to standard out instead of taking
-an explicit Handle. -}
-vprintf :: IOPFRun a => String -> a
-vprintf f = vfprintf stdout f
-
-{- | Utility to force something to a string -}
-ps :: String -> String
-ps = id
-
-{- | Utility to force something to an IO () -}
-pio :: IO () -> IO ()
-pio = id
-
-----------------------------------------------------------------------
--- Documentation for this module
-----------------------------------------------------------------------
-
-{- $introduction
-Welcome to the Haskell printf support.  This module is designed to emulate the
-C printf(3) family of functions.  Here are some quick introductory examples:
-
-
->vsprintf "Hello"
->> "Hello"
->vsprintf "Hello, %s\n" "John"
->> "Hello, John\n"
->vsprintf "%s, your age is %d\n" "John" (10::Integer)
->> "John, your age is 10\n"
-
-Or, using the list-passing method:
-
->sprintf "Hello" []
->> "Hello"
->sprintf "Hello, %s\n" [v "John"]
->> "Hello, John\n"
->sprintf "%s, your age is %d\n" [v "John", v (10::Integer)]
->> "John, your age is 10\n"
-
-Or, using the association list method:
-
->sprintfAL "%(name)s, your age is %(age)d\n"
->  [("name", v "John"),
->   ("age", v (10::Integer))]
->> "John, your age is 10\n"
-
-You can also work with I\/O with these:
-
->main :: IO ()
->main = do
->       pio $ vprintf "Line1\n"
->       pio $ vprintf "Line2: %s\n" "blah"
->       vprintf "Line3: done\n"
-
-This will print @Line1\\nLine2: blah\\nLine3: done\\n@ to standard output.
-You can also use the list form:
-
->main :: IO ()
->main = do
->       printf "Line1\n" []
->       printf "Line2: %s\n" [v "blah"]
->       printf "Line3: done\n" []
-
--}
-
-{- $methodsofuse
-As you can see, there are two different ways to access the printf functions:
-via the variable argument count support (the functions beginning with v)
-or via the list argument support.  There is a utility function, 'v', that
-is simply a shortcut for 'toValue'.
--}
-
-{- $castingnotes
-If you are running in an interactive situation, or something where the
-compiler cannot deduce the expected return type, you will need to cast it
-to @String at .  For instance, at the ghci prompt, you would have to say
-@(sprintf \"foo\")::String@ to make things work.  If you are using one of the
-I\/O variants, you will have to instead cast it to @IO ()@.
-
-To make this easier, there are two functions: 'ps' and 'pio'.  They
-simply provide an easy idiom to force things to the proper type.  Examples:
-
->main :: IO ()
->main = do
->       pio $ vprintf "Line1\n"
->       pio $ vprintf "Line2: %s\n" "blah"
->       vprintf "Line3: done\n"
-
-Note that in this case, no 'pio' was necessary for the third line.
-That's because @main@ was declared to return @IO ()@ already, so the type
-system knows what to do.  If that declaration was missing, the 'pio'
-would have been required there as well.
-
-These special cases apply only to the \"v\" functions.
--}
-
-{- $mappingoutput
-
-As a special extension to the printf() format string syntax, special functions
-can take a key name in the format string.  This key will then be looked up
-in an association list or FiniteMap passed in.  Python programmers will
-find this very similar to Python's @%@ operator, which can look up inside
-dicts.
-
-Here's an example:
-
->import MissingH.Printf
->
->al = [("item1", v "Test One"),
->      ("blah", v (5::Int)),
->      ("zip", v (3.14::Float))]
->
->main :: IO ()
->main = do
->       printfAL "%(item1)s: %(blah)03d, %(zip)06.3f; %(item1)s\n" al
-
-This will print:
-
->Test One: 005, 03.140; Test One
-
--}   
-
-{- $differencesfromc
-These functions are very similar to the C functions.  Here is a list of the
-known differences:
-
-* There is a new conversion type %H.  This will take any type of data
-already converted to a value and display it in its native representation from
-show.  This may not be what you expect for integers, and is likely to be
-altered in the future, so use with caution.
-
-* There is no support for the length specifiers (l, ll, etc.) since Haskell's
-type system provides all the information we need.
-
-* There is no support for the %n, %*, %\$ forms that the C printf() supports.
-These make less sense in Haskell.
-
--}
-
-{- $haskellnotes
-Please be aware of the following as you use this module:
-
-If the type system cannot determine the type of an argument (as in the
-numeric literals in the examples in the introduction), you may have to explicitly cast it to something.
-In practice, this is only a problem in interactive situations like ghci or
-hugs.
-
-Floating-point values are converted to a Double for display.  If you are
-using some floating-point value with an extremely high precision (such
-as a Rational), be aware that some of this precision may be lost for display.x
-
-When run with Hugs, you must use @-98 +o@ on your command line.
-
--}
-
-{- $fullexamples
-
-Here are some full example programs.  You can compile and run these directly.
-
-This example acts as a filter that adds a line number and length to each
-line from input:
-
->import MissingH.Printf
->
->convlines :: Int -> [String] -> [String]
->convlines _ [] = []
->convlines count (line:xs) =
->    vsprintf "%6d, len %03d: %s" count (length line) line : 
->            convlines (count + 1) xs
->
->main = interact $ unlines . convlines 1 . lines
-
-If you have a sample file like this:
-
->Hello,
->
->This is a test.
->Haskell is really neat.
-
-Then running @.\/test < file.txt@ will produce:
-
->     1, len 006: Hello,
->     2, len 000:
->     3, len 015: This is a test.
->     4, len 023: Haskell is really neat.
-
-And so on -- and everything will be nicely lined up since the line numbers
-will grow to the left.
-
-Here's another example of a little bit of interaction:
-
->import MissingH.Printf
->import System.IO
->
->main = do
->       hSetBuffering stdout NoBuffering
->       printf "Welcome.  Please enter your name: " []
->       name <- getLine
->       printf "Hello, %s.  Please enter your age: " [v name]
->       agestr <- getLine
->       let age = (read agestr)::Int
->       printf "%s, you are at least %d months old.\n" [v name, v $ age * 12]
-
-Here's a sample session:
-
->Welcome.  Please enter your name: Bill
->Hello, Bill.  Please enter your age: 53
->Bill, you are at least 636 months old.
-
-The printf functions are also great for creating reports nicely lined up
-by column.  Here's an example:
-
->import MissingH.Printf
->import MissingH.IO
->import Data.List
->
->fmt = "%-10d %010d %010X"
->
->fmtlines :: Int -> [String] -> [String]
->fmtlines _ [] = []
->fmtlines count (x:xs) =
->    let l = length x in
->        vsprintf fmt count l l : fmtlines (count + 1) xs
->
->main = do
->       pio $ vprintf ("%-10s %-10s %s\n") "Line #" "Length Dec" "Length Hex"
->       putStrLn $ (replicate 10 '-') ++ " " ++ (replicate 10 '-') ++
->                " " ++ (replicate 10 '-')
->       lineInteract $ fmtlines 1
-
-When applied to the same example file as before, the output will be:
-
->Line #     Length Dec Length Hex
->---------- ---------- ----------
->1          0000000006 0000000006
->2          0000000000 0000000000
->3          0000000015 000000000F
->4          0000000023 0000000017
-
-There's a full association list example elsewhere in this document.
-
--}
-
diff --git a/MissingH/Printf/Printer.hs b/MissingH/Printf/Printer.hs
deleted file mode 100644
index b7bd843..0000000
--- a/MissingH/Printf/Printer.hs
+++ /dev/null
@@ -1,246 +0,0 @@
-{- arch-tag: Printf printer declarations
-Copyright (C) 2003 Ian Lynagh
-Released under the GNU LGPL 2.1
-See the COPYRIGHT and 3rd-party-licenses/LGPL-2.1 files for more details
--}
-
-{- |
-   Module     : MissingH.Printf.Types
-   Copyright  : Copyright (C) 2003 Ian Lynagh
-   License    : GNU GPL, version 2 or above OR GNU LGPL 2.1
-
-   Maintainer : John Goerzen <jgoerzen at complete.org> 
-   Stability  : provisional
-   Portability: portable
-
-This module is used internally by "MissingH.Printf" and is /not intended
-to be used in your programs/.
-
-Copyright (c) 2003 Ian Lynagh
--}
-
-{- Modified November 2004 by John Goerzen
- * Extracted from Printf 0.1.0 Printer.lhs and Parser.lhs
- * Converted from lhs to hs
- * Converted to work without TH and with my Printf typing system
- * Converted to work with MissingH module names
--}
-
-module MissingH.Printf.Printer (get_conversion_func, thousandify, octalify, hexify, fix_width
-) where
-
-import Maybe (fromMaybe)
-import Numeric (showEFloat, showFFloat)
-import Char (toLower, toUpper)
-import MissingH.Printf.Types
-import Data.List(genericLength, genericReplicate, genericTake)
-
-{-
-xn where n is an integer refers to an argument to the function
-y*, n* is reserved for %n
-fw* is reserved for field width intermediates
-Everything else can be used by the conversion functions
--}
-
-get_conversion_func :: Char -> ConversionFunc
-get_conversion_func c = fromMaybe (error (c:": CF unknown")) $ lookup c cfs
-    where cfs = [
-                 ('d', print_signed_int),
-                 ('i', print_signed_int),
-                 ('o', print_unsigned_int 'o'),
-                 ('u', print_unsigned_int 'u'),
-                 ('x', print_unsigned_int 'x'),
-                 ('X', print_unsigned_int 'X'),
-                 ('e', print_exponent_double 'e'),
-                 ('E', print_exponent_double 'E'),
-                 ('f', print_fixed_double 'f'),
-                 ('F', print_fixed_double 'F'),
-                 -- 'g' not handled
-                 -- 'G' not handled
-                 -- 'a' not handled
-                 -- 'A' not handled
-                 ('c', print_char),
-                 ('s', print_string),
-                 ('C', print_char),
-                 ('S', print_string),
-                 -- 'p' makes no sense
-                 -- 'n' handled elsewhere
-                 -- '%' handled elsewhere
-                 ('H', show_arg) -- Haskell extension
-                ]
-
--- %d, %i
-print_signed_int :: ConversionFunc
-print_signed_int argv flags mw mp = res
-    where arg = (fromValue argv)::Integer
-          preci = fromMaybe 1 mp
-          width = fromMaybe 0 mw
-          disp | Thousands `elem` flags = thousandify . show
-               | otherwise              =               show
-          plus_sign = if Plus `elem` flags
-                      then "+"
-                      else if BlankPlus `elem` flags
-                      then " "
-                      else ""
-          res =    let to_show = toInteger arg
-                       shown = disp $ abs to_show
-                       w = ( if ZeroPadded `elem` flags
-                              then (preci `max` width - genericLength sign)::Width
-                              else (preci)::Width )
-                       sign = if to_show < 0 then "-" else plus_sign
-                       num_zeroes = (w - genericLength shown) `max` 0
-                   in sign ++ genericReplicate num_zeroes '0' ++ shown
-                 
-
--- %o, u, x, X
-print_unsigned_int :: Char -> ConversionFunc
-print_unsigned_int base argv flags mw mp = res
-    where arg = (fromValue argv)::Integer
-          preci = fromMaybe 1  mp
-          width = fromMaybe 0 mw
-          w = if ZeroPadded `elem` flags then (preci) `max` width
-                                         else  preci
-          disp = case base of
-                     'o' -> octalify
-                     'x' -> hexify ({-lift-} lower_hex)
-                     'X' -> hexify ({-lift-} upper_hex)
-                     'u' | Thousands `elem` flags -> thousandify . show
-                         | otherwise              ->                show
-                     _ -> err_letter
-          prefix = if AlternateForm `elem` flags then case base of
-                                                          'o' -> "0"
-                                                          'u' -> ""
-                                                          'x' -> "0x"
-                                                          'X' -> "0X"
-                                                          _ -> err_letter
-                                                 else ""
-          res =    let to_show = toInteger arg `max` 0
-                       shown = disp to_show
-                       pref = if to_show == 0 then "" else prefix
-                       num_zeroes = (w - genericLength shown - genericLength pref) `max` 0
-                   in pref ++ genericReplicate num_zeroes '0' ++ shown
-                 
-          err_letter = error "print_unsigned_int: Bad letter"
-
--- %e, E
-print_exponent_double :: Char -> ConversionFunc
-print_exponent_double e argv flags mw mp = res
-    where arg = (fromValue argv)::Double
-          preci = fromMaybe 6 mp
-          width = fromMaybe 0 mw
-          plus_sign = if Plus `elem` flags
-                      then "+"
-                      else if BlankPlus `elem` flags
-                      then " "
-                      else ""
-          keep_dot = AlternateForm `elem` flags
-          res =    let to_show = (fromRational $ toRational arg) :: Double
-                       shown = showEFloat (Just (fromInteger preci)) (abs to_show) ""
-                       sign = if to_show < 0 then "-" else plus_sign
-                       fix_prec0 = if (preci) == 0
-                                   then case break (== '.') shown of
-                                            (xs, _:_:ys)
-                                                | keep_dot  -> xs ++ '.':ys
-                                                | otherwise -> xs ++ ys
-                                            _ -> shown
-                                   else shown
-                       fix_exp_sign = case break (== 'e') fix_prec0 of
-                                          (xs, 'e':'-':ys) -> xs ++ 'e':'-':ys
-                                          (xs, 'e':ys)     -> xs ++ 'e':'+':ys
-                       fix_exp = case break (== 'e') fix_exp_sign of
-                                     (xs, [_,s,y]) -> xs ++ [e,s,'0',y]
-                                     (xs, _:ys) -> xs ++ e:ys
-                       num_zeroes = (width - genericLength fix_exp - genericLength sign)
-                              `max` 0
-                   in sign ++ genericReplicate num_zeroes '0' ++ fix_exp
-                 
-
--- %f, F
-print_fixed_double :: Char -> ConversionFunc
-print_fixed_double f argv flags mw mp = res
-    where arg = (fromValue argv)::Double
-          preci = fromMaybe 6  mp
-          width = fromMaybe 0  mw
-          plus_sign = if Plus `elem` flags
-                      then "+"
-                      else if BlankPlus `elem` flags
-                      then " "
-                      else ""
-          add_dot = AlternateForm `elem` flags
-          fix_case | f == 'f'  = map toLower
-                   | otherwise = map toUpper
-          res =    let to_show = (fromRational $ toRational arg) :: Double
-                       shown = showFFloat (Just (fromInteger preci)) (abs to_show) ""
-                       shown' = if add_dot && (preci) == 0 then shown ++ "."
-                                                          else shown
-                       sign = if to_show < 0 then "-" else plus_sign
-                       num_zeroes = (width - genericLength shown' - genericLength sign)
-                              `max` 0
-                   in sign ++ genericReplicate num_zeroes '0' ++ fix_case shown'
-                 
-
--- %c, C
-print_char :: ConversionFunc
-print_char arg _ _ _ = [(fromValue arg)::Char]
-
--- %s, S
-print_string :: ConversionFunc
-print_string argv _ _ mp
-    = case mp of
-          Just preci -> if preci < 0 then arg else genericTake preci arg
-          Nothing -> arg
-      where arg = fromValue argv
-
--- Corresponds to %H (Haskell extension)
-show_arg :: ConversionFunc
-show_arg argv flags mw mp = (print_string (toValue (showValue argv))) flags mw mp
-
-lower_hex, upper_hex :: Bool
-lower_hex = False
-upper_hex = True
-
-hexify :: Bool -> Integer -> String
-hexify _ 0 = "0"
-hexify upper i = to_base 16 ((digits !!) . fromInteger) i
-    where digits | upper     = ['0'..'9'] ++ ['A'..'F']
-                 | otherwise = ['0'..'9'] ++ ['a'..'f']
-
-octalify :: Integer -> String
-octalify 0 = "0"
-octalify i = to_base 8 ((['0'..'7'] !!) . fromInteger) i
-
-to_base :: Integer           -- Base
-        -> (Integer -> Char) -- Digit maker
-        -> Integer           -- Number to convert, > 0
-        -> String
-to_base = f ""
-    where f s _    _       0 = s
-          f s base mkDigit i = case i `divMod` base of
-                                   (i', d) -> f (mkDigit d:s) base mkDigit i'
-
-thousandify :: String -> String
-thousandify = reverse . t . reverse
-    where t (x1:x2:x3:xs@(_:_)) = x1:x2:x3:',':t xs
-          t xs = xs
-
-
-----------------------------------------------------------------------
--- FROM Ian Lynagh's Parser.lhs
-----------------------------------------------------------------------
-
-
-fix_width :: [Flag] -> Maybe Width -> String -> String
-fix_width _ Nothing e = e
-fix_width flags (Just w) e = exp_spaced
-    where
-          exp_num_spaces = abs w - genericLength e
-          exp_num_spaces' = 0 `max` exp_num_spaces
-          exp_spaces = genericReplicate exp_num_spaces' ' '
-          exp_left_padded = e ++ exp_spaces
-          exp_right_padded = exp_spaces ++ e
-          exp_spaced = if LeftAdjust `elem` flags
-                       then exp_left_padded
-                       else if w < 0 then exp_left_padded
-                                      else exp_right_padded
-
-
diff --git a/MissingH/Printf/Types.hs b/MissingH/Printf/Types.hs
deleted file mode 100644
index 3f5cbf2..0000000
--- a/MissingH/Printf/Types.hs
+++ /dev/null
@@ -1,166 +0,0 @@
-{- arch-tag: Printf type declarations
-Copyright (C) 2004 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
-
-Portions Copyright (c) 2003 Ian Lynagh and released under the GNU LGPL 2.1.
--}
-
-{- |
-   Module     : MissingH.Printf.Types
-   Copyright  : Copyright (C) 2004 John Goerzen; (C) 2003 Ian Lynagh
-   License    : GNU GPL, version 2 or above
-
-   Maintainer : John Goerzen <jgoerzen at complete.org> 
-   Stability  : provisional
-   Portability: portable
-
-This module is used internally by "MissingH.Printf" and is /not intended
-to be used in your programs/.
-
-Copyright (c) 2004 John Goerzen, jgoerzen\@complete.org
-
-Portions Copyright (c) 2003 Ian Lynagh
--}
-
--- Begin John Goerzen's code  
- 
-module MissingH.Printf.Types where
-
-import System.IO
-import Data.Ratio
-import Data.FiniteMap
-
--- data Wrapped a = Wrapped a
-
-{- | All items to be printed must be expressible as one of these. -}
-data Value =
-           ValueRational Rational
-           | ValueString String
-           | ValueChar Char
-             deriving (Eq, Show, Ord)
-
-showValue :: Value -> String
-showValue (ValueRational x) = show x
-showValue (ValueChar x) = [x]
-showValue (ValueString x) = x
-
-{- | The class to which all items must belong (unless you want to inconvenience
-everyone and force them to manually generate 'Value's.
--}
-class PFType a where
-    toValue :: a -> Value
-    fromValue :: Value -> a
-
-instance (Real a) => PFType a where
-    toValue = ValueRational . toRational
-    fromValue = error "fromValue to generic Real not supported"--fromRational . fromValue
-
-instance PFType Integer where
-    toValue = ValueRational . toRational
-    fromValue (ValueRational x) = 
-        if denominator x == 1
-           then toInteger $ numerator x
-           else error ("Can't make an int from non-integral rational " ++ show x)
-    fromValue _ = error "fromValue integer"
-
-instance PFType Double where
-    toValue = ValueRational . toRational
-    fromValue (ValueRational x) = fromRational x
-    fromValue _ = error "fromValue Double"
-
-instance PFType String where
-    toValue = ValueString
-    fromValue (ValueString x) = x
-    fromValue _ = error "fromValue string"
-
-instance PFType Char where
-    toValue = ValueChar
-    fromValue (ValueChar x) = x
-    fromValue _ = error "fromValue char"
-
-{-
-instance PFType Double where
-    toValue = ValueDouble
-    fromValue (ValueDouble x) = x
-    fromValue _ = error "fromValue Double"
--}
-{-
-instance PFType Value where
-    toValue = id
-    fromValue = id
--}
-class PFRun a where
-    pfrun :: ([Value] -> String) -> a
-instance PFRun String where
-    pfrun f = f $ []
-instance (PFType a, PFRun b) => PFRun (a -> b) where
-    pfrun f x = 
-        let nextfunc xs = f ((toValue x) : xs)
-            in
-            pfrun nextfunc
-
-class IOPFRun a where
-    iopfrun :: Handle -> ([Value] -> String) -> a
-instance IOPFRun (IO ()) where
-    iopfrun h f = hPutStr h $ pfrun f
-instance (PFType a, IOPFRun b) => IOPFRun (a -> b) where
-    iopfrun h f x = iopfrun h (\xs -> f (toValue x : xs))
-
-{-
--------------------------------------------
--- Begin code from Ian Lynagh
--- Copyright (c) 2003 Ian Lynagh.  Released under the GNU LGPL 2.1.
-
-Modified November 2004 by John Goerzen:
- * Extraced from Printf sources
- * Removed code I don't need
- * Converted to work without TH
- * Converted to work with MissingH module names
--}
-
-type ConversionFunc = Arg
-                   -> [Flag]
-                   -> Maybe Width
-                   -> Maybe Precision
-                   -> String
-
-data Format = Literal String
-            | Conversion ConversionFunc
-            | CharCount
-
-type ArgNum = Integer
-type Arg = Value
-type Width = Integer
-type Precision = Integer
-data Flag = AlternateForm       -- "#"
-          | ZeroPadded          -- "0"
-          | LeftAdjust          -- "-"
-          | BlankPlus           -- " "
-          | Plus                -- "+"
-          | Thousands           -- "'"
-          | AlternativeDigits   -- "I" (ignored)
-    deriving (Eq, Show)
-
-xvar :: ArgNum -> String
-xvar i = 'x':show i
-
-yvar :: ArgNum -> String
-yvar i = 'y':show i
-
-nvar :: ArgNum -> String
-nvar i = 'n':show i
-
-

-- 
haskell-testpack



More information about the Pkg-haskell-commits mailing list