Added documentation to PrettyShow and ShowCode, along with an export list for the latter.
This commit is contained in:
parent
75ae6fa36f
commit
deef9dd209
|
@ -20,6 +20,15 @@ with this program. If not, see <http://www.gnu.org/licenses/>.
|
|||
-- This ought to use a class (like show does), so that it can be extended
|
||||
-- properly without me needing to have Tock-specific cases in here -- see the
|
||||
-- appropriate SYB paper.
|
||||
--
|
||||
-- PrettyShow exports two functions: pshow and pshowCode. pshow works
|
||||
-- much like 'gshow', but it uses the 'Text.PrettyPrint.HughesPJ' module
|
||||
-- to render the text with line-breaks and such.
|
||||
--
|
||||
-- pshowCode uses the 'ShowOccam' and 'ShowRain' type-classes wherever possible
|
||||
-- (via the 'extCode' function) to print out data, otherwise it acts
|
||||
-- like pshow. Note that because pshowCode chooses the appropriate
|
||||
-- language based on the 'csFrontend' in 'CompState', it is inside the CSM monad.
|
||||
module PrettyShow (pshow, pshowCode) where
|
||||
|
||||
import Control.Monad.State
|
||||
|
|
|
@ -19,7 +19,7 @@ with this program. If not, see <http://www.gnu.org/licenses/>.
|
|||
|
||||
-- | A module with type-classes and functions for displaying code, dependent on the context.
|
||||
-- Primarily, this means showing code as occam in error messages for the occam frontend, and Rain code for the Rain frontend.
|
||||
module ShowCode where
|
||||
module ShowCode (showCode, showOccam, showRain, formatCode, extCode) where
|
||||
|
||||
import Control.Monad.State
|
||||
import Data.Generics
|
||||
|
@ -176,6 +176,12 @@ instance ShowRain A.Variable where
|
|||
showRain x = "<invalid Rain variable: " ++ show x ++ ">"
|
||||
|
||||
-- | Extends an existing (probably generic) function with cases for everything that has a specific ShowOccam and ShowRain instance
|
||||
-- This is a bit of manual wiring. Because we can't generically deduce whether or not
|
||||
-- a given Data item has a showRain/showOccam implementation (that I know of), I have
|
||||
-- had to add this function that has a line for each type that does have a
|
||||
-- ShowOccam/ShowRain implementation. But since to add a type to the ShowOccam/ShowRain
|
||||
-- classes you have to provide a specific instance above anyway, I don't think that adding
|
||||
-- one more line while you're at it is too bad.
|
||||
extCode :: Typeable b => (b -> Doc) -> (forall a. (ShowOccam a, ShowRain a) => a -> String) -> (b -> Doc)
|
||||
extCode q f = q `extQ` (text . (f :: A.Type -> String))
|
||||
`extQ` (text . (f :: A.DyadicOp -> String))
|
||||
|
|
Loading…
Reference in New Issue
Block a user