uhc-util-0.1.1.0: UHC utilities

Safe HaskellNone

UHC.Util.CompileRun

Synopsis

Documentation

data CompileRun nm unit info err Source

Constructors

CompileRun 

Fields

crCUCache :: Map nm unit
 
crCompileOrder :: [[nm]]
 
crTopModNm :: nm
 
crState :: CompileRunState err
 
crStateInfo :: info
 

type CompilePhase n u i e a = StateT (CompileRun n u i e) IO aSource

class CompileUnit u n l s | u -> n l s whereSource

Methods

cuDefault :: uSource

cuFPath :: u -> FPathSource

cuUpdFPath :: FPath -> u -> uSource

cuLocation :: u -> lSource

cuUpdLocation :: l -> u -> uSource

cuKey :: u -> nSource

cuUpdKey :: n -> u -> uSource

cuState :: u -> sSource

cuUpdState :: s -> u -> uSource

cuImports :: u -> [n]Source

cuParticipation :: u -> [CompileParticipation]Source

class FPathError e => CompileRunError e p | e -> p whereSource

Instances

class CompileModName n whereSource

Methods

mkCMNm :: String -> nSource

class CompileRunStateInfo i n p whereSource

Methods

crsiImportPosOfCUKey :: n -> i -> pSource

class FileLocatable x loc | loc -> x whereSource

Methods

fileLocation :: x -> locSource

noFileLocation :: locSource

mkEmptyCompileRun :: n -> i -> CompileRun n u i eSource

crCU :: (Show n, Ord n) => n -> CompileRun n u i e -> uSource

crMbCU :: Ord n => n -> CompileRun n u i e -> Maybe uSource

ppCR :: (PP n, PP u) => CompileRun n u i e -> PP_DocSource

cpUpdStateInfo :: (i -> i) -> CompilePhase n u i e ()Source

cpUpdSI :: (i -> i) -> CompilePhase n u i e ()Source

cpUpdCU :: (Ord n, CompileUnit u n l s) => n -> (u -> u) -> CompilePhase n u i e ()Source

cpUpdCUWithKey :: (Ord n, CompileUnit u n l s) => n -> (n -> u -> (n, u)) -> CompilePhase n u i e nSource

cpSetErrs :: [e] -> CompilePhase n u i e ()Source

cpSetLimitErrs :: Int -> String -> [e] -> CompilePhase n u i e ()Source

cpSetLimitErrsWhen :: Int -> String -> [e] -> CompilePhase n u i e ()Source

cpSetInfos :: String -> Bool -> [e] -> CompilePhase n u i e ()Source

cpSetCompileOrder :: [[n]] -> CompilePhase n u i e ()Source

cpSeq :: CompileRunError e p => [CompilePhase n u i e ()] -> CompilePhase n u i e ()Source

cpSeqWhen :: CompileRunError e p => Bool -> [CompilePhase n u i e ()] -> CompilePhase n u i e ()Source

cpFindFilesForFPathInLocations :: (Ord n, FPATH n, FileLocatable u loc, Show loc, CompileUnitState s, CompileRunError e p, CompileUnit u n loc s, CompileModName n, CompileRunStateInfo i n p) => (loc -> n -> FPath -> [(loc, FPath, [e])]) -> ((FPath, loc, [e]) -> res) -> Bool -> [(FileSuffix, s)] -> [loc] -> Maybe n -> Maybe FPath -> CompilePhase n u i e [res]Source

cpImportGather :: (Show n, Ord n, CompileUnit u n l s, CompileRunError e p, CompileUnitState s) => (n -> CompilePhase n u i e ()) -> n -> CompilePhase n u i e ()Source

Abbreviation for cpImportGatherFromMods for 1 module

cpImportGatherFromMods :: (Show n, Ord n, CompileUnit u n l s, CompileRunError e p, CompileUnitState s) => (Maybe prev -> n -> CompilePhase n u i e (x, Maybe prev)) -> [n] -> CompilePhase n u i e ()Source

recursively extract imported modules

cpImportGatherFromModsWithImp :: (Show n, Ord n, CompileUnit u n l s, CompileRunError e p, CompileUnitState s) => (u -> [n]) -> (Maybe prev -> n -> CompilePhase n u i e (x, Maybe prev)) -> [n] -> CompilePhase n u i e ()Source

recursively extract imported modules, providing a way to import + do the import

cpPP :: (PP n, PP u) => String -> CompilePhase n u i e ()Source

cpPPMsg :: PP m => m -> CompilePhase n u i e ()Source

forgetM :: Monad m => m a -> m ()Source