{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE UndecidableInstances #-} module Numeric.LAPACK.Format ( (##), print, hyper, Format(format), FormatArray(formatArray), ArrFormat.deflt, defltConfig, Config(..), ) where import qualified Numeric.LAPACK.Matrix.Type.Private as Matrix 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.Private (Matrix) import Numeric.LAPACK.Matrix.Plain.Format (Config(..), defltConfig, FormatArray, formatArray, printfFloating) 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) => Config -> a -> IO () print cfg a = putStr $ trim $ TextBox.render $ format cfg a (##) :: (Format a) => a -> String -> IO () a##cfg = print (defltConfig {configFormat = cfg}) a trim :: String -> String trim = unlines . map (ListRev.dropWhile isSpace) . lines hyper :: (Format a) => Config -> a -> Hyper.Graphic hyper cfg = Output.hyper . format cfg class Format a where format :: (Output out) => Config -> a -> out instance Format Int where format _cfg = Output.text . show instance Format Float where format cfg = Output.text . printf (configFormat cfg) instance Format Double where format cfg = Output.text . printf (configFormat cfg) instance (Class.Real a) => Format (Complex a) where format cfg = Output.text . fold . printfFloating cfg instance (Format a) => Format [a] where format cfg = Output.formatColumn . map (format cfg) instance (Format a, Format b) => Format (a,b) where format cfg (a,b) = format cfg a /+/ format cfg b instance (Format a, Format b, Format c) => Format (a,b,c) where format cfg (a,b,c) = format cfg a /+/ format cfg b /+/ format cfg c instance (Shape.C sh) => Format (Perm.Permutation sh) where format _cfg = Perm.format instance (FormatArray sh, Class.Floating a) => Format (Array sh a) where format = formatArray instance (Matrix.Format typ, Matrix.FormatExtra typ xl, Matrix.FormatExtra typ xu, Extent.Measure meas, Extent.C vert, Extent.C horiz, Shape.C height, Shape.C width, Class.Floating a) => Format (Matrix typ xl xu lower upper meas vert horiz height width a) where format = Matrix.format