{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE FlexibleInstances #-} ----------------------------------------------------------------------------- -- | -- Module : Windll -- Copyright : (c) Tamar Christina 2009 - 2010 -- License : BSD3 -- -- Maintainer : tamar@zhox.com -- Stability : experimental -- Portability : portable -- -- MShow class definition -- ----------------------------------------------------------------------------- module WinDll.Structs.MShow.MShow where -- * A custom show class class MShow a where mshow :: a -> String mshowList :: [a] -> String mshowList = unlines.map mshow mshowM :: Int -> a -> String mshowM _ = mshow mshowWithPath :: Bool -> String -> String -> String -> a -> String mshowWithPath _ _ _ _ = mshow mshowListWithPath :: Bool -> String -> String -> String -> [a] -> String mshowListWithPath a b c d = unlines.map (mshowWithPath a b c d) instance MShow String where mshow = id instance MShow a => MShow (Maybe a) where mshow Nothing = "" mshow (Just a) = mshow a -- | Indenting size tabstop :: Int tabstop = 4 -- | A function to Indent things along. indent :: String -> String indent = ((replicate tabstop ' ') ++) -- | A function to Indent things halfway along. indent' :: String -> String indent' = ((replicate (tabstop `div` 2) ' ') ++) -- | A function to Inline structure inline :: String -> String inline = drop tabstop