{-# LANGUAGE TypeFamilies #-} module Numeric.LAPACK.Format ( (##), print, hyper, Format(format), FormatArray(formatArray), FormatMatrix(formatMatrix), ArrFormat.deflt, ) where import qualified Numeric.LAPACK.Matrix.Plain.Format as ArrFormat import qualified Numeric.LAPACK.Matrix.Extent.Private as Extent import qualified Numeric.LAPACK.Output as Output import qualified Numeric.LAPACK.Permutation.Private as Perm import Numeric.LAPACK.Matrix.Type (Matrix, FormatMatrix(formatMatrix)) import Numeric.LAPACK.Matrix.Plain.Format (FormatArray, formatArray, printfComplex) import Numeric.LAPACK.Output (Output, (/+/)) import qualified Numeric.Netlib.Class as Class import qualified Data.Array.Comfort.Shape as Shape import Data.Array.Comfort.Storable (Array) import qualified Text.PrettyPrint.Boxes as TextBox import qualified Hyper import Text.Printf (printf) import qualified Data.List.Reverse.StrictSpine as ListRev import Data.Foldable (fold) import Data.Complex (Complex) import Data.Char (isSpace) import Prelude hiding (print) infix 0 ## print :: (Format a) => String -> a -> IO () print fmt a = putStr $ trim $ TextBox.render $ format fmt a (##) :: (Format a) => a -> String -> IO () (##) = flip print trim :: String -> String trim = unlines . map (ListRev.dropWhile isSpace) . lines hyper :: (Format a) => String -> a -> Hyper.Graphic hyper fmt = Output.hyper . format fmt class Format a where format :: (Output out) => String -> a -> out instance Format Int where format _fmt = Output.text . show instance Format Float where format fmt = Output.text . printf fmt instance Format Double where format fmt = Output.text . printf fmt instance (Class.Real a) => Format (Complex a) where format fmt = Output.text . fold . printfComplex fmt instance (Format a) => Format [a] where format fmt = Output.formatColumn . map (format fmt) instance (Format a, Format b) => Format (a,b) where format fmt (a,b) = format fmt a /+/ format fmt b instance (Format a, Format b, Format c) => Format (a,b,c) where format fmt (a,b,c) = format fmt a /+/ format fmt b /+/ format fmt c instance (Shape.C sh) => Format (Perm.Permutation sh) where format _fmt = Perm.format instance (FormatArray sh, Class.Floating a) => Format (Array sh a) where format = formatArray instance (FormatMatrix typ, Extent.Measure meas, Extent.C vert, Extent.C horiz, Shape.C width, Shape.C height, Class.Floating a) => Format (Matrix typ xl xu lower upper meas vert horiz height width a) where format = formatMatrix