-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | UHC utilities -- -- General purpose utilities for UHC and related tools @package uhc-util @version 0.1.3.2 module UHC.Util.VarLookup -- | VarLookup abstracts from a Map. The purpose is to be able to combine -- maps only for the purpose of searching without actually merging the -- maps. This then avoids the later need to unmerge such mergings. The -- class interface serves to hide this. class VarLookup m k v where varlookup = varlookupWithMetaLev 0 varlookupWithMetaLev :: VarLookup m k v => MetaLev -> k -> m -> Maybe v varlookup :: VarLookup m k v => k -> m -> Maybe v varlookupMap :: VarLookup m k v => (v -> Maybe res) -> k -> m -> Maybe res type VarLookupFix k v = k -> Maybe v -- | fix looking up to be for a certain var mapping varlookupFix :: VarLookup m k v => m -> VarLookupFix k v -- | simulate deletion varlookupFixDel :: Ord k => [k] -> VarLookupFix k v -> VarLookupFix k v -- | VarLookupCmb abstracts the combining of/from a substitution. -- The interface goes along with VarLookup but is split off to avoid -- functional dependency restrictions. The purpose is to be able to -- combine maps only for the purpose of searching without actually -- merging the maps. This then avoids the later need to unmerge such -- mergings. class VarLookupCmb m1 m2 (|+>) :: VarLookupCmb m1 m2 => m1 -> m2 -> m2 class VarLookupBase m k v | m -> k v varlookupEmpty :: VarLookupBase m k v => m type VarLookupCmbFix m1 m2 = m1 -> m2 -> m2 -- | fix combining up to be for a certain var mapping varlookupcmbFix :: VarLookupCmb m1 m2 => VarLookupCmbFix m1 m2 -- | Level to lookup into type MetaLev = Int -- | Base level (of values, usually) metaLevVal :: MetaLev instance [overlap ok] (VarLookupCmb m1 m1, VarLookupCmb m1 m2) => VarLookupCmb [m1] [m2] instance [overlap ok] VarLookupCmb m1 m2 => VarLookupCmb m1 [m2] instance [overlap ok] VarLookup m k v => VarLookup [m] k v instance [overlap ok] (VarLookup m1 k v, VarLookup m2 k v) => VarLookup (m1, m2) k v module UHC.Util.Rel type Rel a b = Set (a, b) empty :: Rel a b toList :: Rel a b -> [(a, b)] fromList :: (Ord a, Ord b) => [(a, b)] -> Rel a b singleton :: (Ord a, Ord b) => a -> b -> Rel a b dom :: (Ord a, Ord b) => Rel a b -> Set a rng :: (Ord a, Ord b) => Rel a b -> Set b restrictDom :: (Ord a, Ord b) => (a -> Bool) -> Rel a b -> Rel a b restrictRng :: (Ord a, Ord b) => (b -> Bool) -> Rel a b -> Rel a b mapDom :: (Ord a, Ord b, Ord x) => (a -> x) -> Rel a b -> Rel x b mapRng :: (Ord a, Ord b, Ord x) => (b -> x) -> Rel a b -> Rel a x partitionDom :: (Ord a, Ord b) => (a -> Bool) -> Rel a b -> (Rel a b, Rel a b) partitionRng :: (Ord a, Ord b) => (b -> Bool) -> Rel a b -> (Rel a b, Rel a b) intersection :: (Ord a, Ord b) => Rel a b -> Rel a b -> Rel a b difference :: (Ord a, Ord b) => Rel a b -> Rel a b -> Rel a b union :: (Ord a, Ord b) => Rel a b -> Rel a b -> Rel a b unions :: (Ord a, Ord b) => [Rel a b] -> Rel a b apply :: (Ord a, Ord b) => Rel a b -> a -> [b] toDomMap :: Ord a => Rel a b -> Map a [b] toRngMap :: Ord b => Rel a b -> Map b [a] mapDomRng :: (Ord a, Ord b, Ord a', Ord b') => ((a, b) -> (a', b')) -> Rel a b -> Rel a' b' module UHC.Util.PrettySimple type PP_Doc = Doc -- | Interface for PP class Show a => PP a where pp = text . show ppList as = hlist as pp :: PP a => a -> PP_Doc ppList :: PP a => [a] -> PP_Doc -- | Display to string disp :: PP_Doc -> Int -> ShowS -- | Display to Handle hPut :: Handle -> PP_Doc -> Int -> IO () -- | PP horizontally aside (>|<) :: (PP a, PP b) => a -> b -> PP_Doc -- | PP vertically above (>-<) :: (PP a, PP b) => a -> b -> PP_Doc -- | PP horizontally aside with 1 blank in between (>#<) :: (PP a, PP b) => a -> b -> PP_Doc -- | PP list vertically hlist :: PP a => [a] -> PP_Doc -- | PP list horizontally vlist :: PP a => [a] -> PP_Doc -- | PP list vertically, alias for vlist hv :: PP a => [a] -> PP_Doc -- | PP list horizontally, alias for hlist fill :: PP a => [a] -> PP_Doc -- | Indent indent :: PP a => Int -> a -> PP_Doc -- | empty PP empty :: PP_Doc -- | basic string text :: String -> PP_Doc -- | Is single line doc? isSingleLine :: PP_Doc -> Bool instance PP Float instance PP Integer instance PP Int instance Show PP_Doc instance PP a => PP [a] instance PP Char instance PP PP_Doc module UHC.Util.ParseUtils type PlainParser tok gp = IsParser p tok => p gp type LayoutParser tok ep = (IsParser (OffsideParser i o tok p) tok, InputState i tok p, OutputState o, Position p) => OffsideParser i o tok p ep type LayoutParser2 tok ep = (IsParser (OffsideParser i o tok p) tok, InputState i tok p, OutputState o, Position p) => OffsideParser i o tok p ep -> OffsideParser i o tok p ep parsePlain :: (Symbol s, InputState inp s pos) => AnaParser inp Pair s pos a -> inp -> Steps (a, inp) s pos parseOffsideToResMsgs :: (Symbol s, InputState i s p, Position p) => OffsideParser i Pair s p a -> OffsideInput i s p -> (a, [Message (OffsideSymbol s) p]) parseToResMsgs :: (Symbol s, InputState inp s pos) => AnaParser inp Pair s pos a -> inp -> (a, [Message s pos]) parseOffsideToResMsgsStopAtErr :: (Symbol s, InputState i s p, Position p) => OffsideParser i Pair s p a -> OffsideInput i s p -> (a, [Message (OffsideSymbol s) p]) pAnyFromMap :: IsParser p s => (k -> p a1) -> Map k v -> p v pAnyKey :: IsParser p s => (a1 -> p a) -> [a1] -> p a pMaybe :: IsParser p s => a1 -> (a -> a1) -> p a -> p a1 pMb :: IsParser p s => p a -> p (Maybe a) pDo :: (InputState i s p, OutputState o, Position p, Symbol s, Ord s) => OffsideParser i o s p x -> OffsideParser i o s p y -> OffsideParser i o s p z -> OffsideParser i o s p a -> OffsideParser i o s p (Maybe last -> a) -> OffsideParser i o s p last -> OffsideParser i o s p [a] module UHC.Util.Time -- | a for now alias for old-time ClockTime type ClockTime = UTCTime diffClockTimes :: UTCTime -> UTCTime -> NominalDiffTime noTimeDiff :: NominalDiffTime getClockTime :: IO ClockTime -- | Extensions to Control.Monad module UHC.Util.Control.Monad liftM6 :: Monad m => (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m a6 -> m r liftM7 :: Monad m => (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m a6 -> m a7 -> m r liftM8 :: Monad m => (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m a6 -> m a7 -> m a8 -> m r liftM9 :: Monad m => (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m a6 -> m a7 -> m a8 -> m a9 -> m r module UHC.Util.Utils unionMapSet :: Ord b => (a -> Set b) -> (Set a -> Set b) inverseMap :: (Ord k, Ord v') => (k -> v -> (v', k')) -> Map k v -> Map v' k' showStringMapKeys :: Map String x -> String -> String hdAndTl' :: a -> [a] -> (a, [a]) hdAndTl :: [a] -> (a, [a]) maybeNull :: r -> ([a] -> r) -> [a] -> r maybeHd :: r -> (a -> r) -> [a] -> r wordsBy :: (a -> Bool) -> [a] -> [[a]] initlast :: [a] -> Maybe ([a], a) -- | variation on last which returns empty value instead of last' :: a -> [a] -> a initlast2 :: [a] -> Maybe ([a], a, a) firstNotEmpty :: [[x]] -> [x] listSaturate :: (Enum a, Ord a) => a -> a -> (x -> a) -> (a -> x) -> [x] -> [x] listSaturateWith :: (Enum a, Ord a) => a -> a -> (x -> a) -> [(a, x)] -> [x] -> [x] spanOnRest :: ([a] -> Bool) -> [a] -> ([a], [a]) tup123to1 :: (t, t1, t2) -> t tup123to2 :: (t, t1, t2) -> t1 tup123to12 :: (t1, t2, t) -> (t1, t2) tup123to23 :: (t, t1, t2) -> (t1, t2) tup12to123 :: t2 -> (t, t1) -> (t, t1, t2) strWhite :: Int -> String strPad :: String -> Int -> String strCapitalize :: String -> String strToInt :: String -> Int splitForQualified :: String -> [String] panic :: [Char] -> t isSortedByOn :: (b -> b -> Ordering) -> (a -> b) -> [a] -> Bool sortOn :: Ord b => (a -> b) -> [a] -> [a] sortByOn :: (b -> b -> Ordering) -> (a -> b) -> [a] -> [a] groupOn :: Eq b => (a -> b) -> [a] -> [[a]] groupSortOn :: Ord b => (a -> b) -> [a] -> [[a]] groupByOn :: (b -> b -> Bool) -> (a -> b) -> [a] -> [[a]] groupSortByOn :: (b -> b -> Ordering) -> (a -> b) -> [a] -> [[a]] nubOn :: Eq b => (a -> b) -> [a] -> [a] -- | The consecutiveBy function groups like groupBy, but based on a -- function which says whether 2 elements are consecutive consecutiveBy :: (a -> a -> Bool) -> [a] -> [[a]] -- | Partition, but also return a function which will rebuild according to -- the original ordering of list elements partitionAndRebuild :: (v -> Bool) -> [v] -> ([v], [v], [v'] -> [v'] -> [v']) orderingLexic :: [Ordering] -> Ordering panicJust :: String -> Maybe a -> a ($?) :: (a -> Maybe b) -> Maybe a -> Maybe b orMb :: Maybe a -> Maybe a -> Maybe a maybeAnd :: x -> (a -> b -> x) -> Maybe a -> Maybe b -> x maybeOr :: x -> (a -> x) -> (b -> x) -> Maybe a -> Maybe b -> x scc :: Ord n => [(n, [n])] -> [[n]] -- | double lookup, with transformer for 2nd map mapLookup2' :: (Ord k1, Ord k2) => (v1 -> Map k2 v2) -> k1 -> k2 -> Map k1 v1 -> Maybe (Map k2 v2, v2) -- | double lookup mapLookup2 :: (Ord k1, Ord k2) => k1 -> k2 -> Map k1 (Map k2 v2) -> Maybe v2 -- | loop over monads yielding a Maybe from a start value, yielding the -- first Just or the start (when no Just is returned) firstMaybeM :: Monad m => a -> [a -> m (Maybe a)] -> m a module UHC.Util.FPath data FPath FPath :: !(Maybe String) -> !String -> !(Maybe String) -> FPath fpathMbDir :: FPath -> !(Maybe String) fpathBase :: FPath -> !String fpathMbSuff :: FPath -> !(Maybe String) fpathSuff :: FPath -> String class FPATH f mkFPath :: FPATH f => f -> FPath class FPathError e emptyFPath :: FPath fpathFromStr :: String -> FPath mkFPathFromDirsFile :: Show s => [s] -> s -> FPath fpathToStr :: FPath -> String fpathIsEmpty :: FPath -> Bool fpathSetBase :: String -> FPath -> FPath fpathSetSuff :: String -> FPath -> FPath fpathSetDir :: String -> FPath -> FPath fpathUpdBase :: (String -> String) -> FPath -> FPath fpathRemoveSuff :: FPath -> FPath fpathRemoveDir :: FPath -> FPath fpathIsAbsolute :: FPath -> Bool fpathAppendDir :: FPath -> String -> FPath fpathUnAppendDir :: FPath -> String -> FPath fpathPrependDir :: String -> FPath -> FPath fpathUnPrependDir :: String -> FPath -> FPath fpathSplitDirBy :: String -> FPath -> Maybe (String, String) mkTopLevelFPath :: String -> String -> FPath fpathDirSep :: String fpathDirSepChar :: Char fpathOpenOrStdin :: FPath -> IO (FPath, Handle) openFPath :: FPath -> IOMode -> Bool -> IO (String, Handle) type SearchPath = [String] type FileSuffixes = [FileSuffix] type FileSuffix = Maybe String mkInitSearchPath :: FPath -> SearchPath searchPathFromFPath :: FPath -> SearchPath searchPathFromFPaths :: [FPath] -> SearchPath searchPathFromString :: String -> [String] searchFPathFromLoc :: FilePath -> FPath -> [(FilePath, FPath)] searchLocationsForReadableFiles :: FPathError e => (loc -> FPath -> [(loc, FPath, [e])]) -> Bool -> [loc] -> FileSuffixes -> FPath -> IO [(FPath, loc, [e])] searchPathForReadableFiles :: Bool -> SearchPath -> FileSuffixes -> FPath -> IO [FPath] searchPathForReadableFile :: SearchPath -> FileSuffixes -> FPath -> IO (Maybe FPath) fpathEnsureExists :: FPath -> IO () filePathMkPrefix :: String -> String filePathUnPrefix :: String -> String filePathCoalesceSeparator :: String -> String filePathMkAbsolute :: String -> String filePathUnAbsolute :: String -> String fpathGetModificationTime :: FPath -> IO UTCTime instance Show FPath instance Eq FPath instance Ord FPath instance FPathError String instance FPATH FPath instance FPATH String module UHC.Util.Binary -- | Decode from Handle hGetBinary :: Binary a => Handle -> IO a -- | Decode from FilePath getBinaryFile :: Binary a => FilePath -> IO a -- | Decode from FilePath getBinaryFPath :: Binary a => FPath -> IO a -- | Encode to Handle hPutBinary :: Binary a => Handle -> a -> IO () -- | Encode to FilePath putBinaryFile :: Binary a => FilePath -> a -> IO () -- | Encode to FPath, ensuring existence of path putBinaryFPath :: Binary a => FPath -> a -> IO () -- | put an Enum putEnum :: Enum x => x -> Put -- | get an Enum getEnum :: Enum x => Get x -- | put an Enum as Word8 putEnum8 :: Enum x => x -> Put -- | get an Enum from Word8 getEnum8 :: Enum x => Get x -- | put a [] putList :: (Binary a, Binary b) => (x -> Bool) -> (x -> (a, b)) -> x -> Put -- | get a [] getList :: (Binary a, Binary b) => x -> (a -> b -> x) -> Get x module UHC.Util.FastSeq data FastSeq a (:++:) :: !(FastSeq a) -> !(FastSeq a) -> FastSeq a (:+::) :: !a -> !(FastSeq a) -> FastSeq a (::+:) :: !(FastSeq a) -> !a -> FastSeq a type Seq a = FastSeq a isEmpty :: FastSeq a -> Bool null :: FastSeq a -> Bool empty :: FastSeq a size :: FastSeq a -> Int singleton :: a -> FastSeq a toList :: FastSeq a -> [a] fromList :: [a] -> FastSeq a map :: (a -> b) -> FastSeq a -> FastSeq b union :: FastSeq a -> FastSeq a -> FastSeq a unions :: [FastSeq a] -> FastSeq a firstNotEmpty :: [FastSeq x] -> FastSeq x instance Monoid (FastSeq a) module UHC.Util.Serialize type SPut = State SPutS () type SGet x = StateT SGetS Get x class Serialize x where sputNested = panic "not implemented (must be done by instance): Serialize.sputNested" sgetNested = panic "not implemented (must be done by instance): Serialize.sgetNested" sput :: Serialize x => x -> SPut sget :: Serialize x => SGet x sputNested :: Serialize x => x -> SPut sgetNested :: Serialize x => SGet x sputPlain :: (Binary x, Serialize x) => x -> SPut sgetPlain :: (Binary x, Serialize x) => SGet x sputUnshared :: (Binary x, Serialize x) => x -> SPut sputShared :: (Ord x, Serialize x, Typeable x) => x -> SPut sgetShared :: (Ord x, Serialize x, Typeable x) => SGet x sputWord8 :: Word8 -> SPut sgetWord8 :: SGet Word8 sputWord16 :: Word16 -> SPut sgetWord16 :: SGet Word16 sputEnum8 :: Enum x => x -> SPut sgetEnum8 :: Enum x => SGet x runSPut :: SPut -> Put runSGet :: SGet x -> Get x serialize :: Serialize x => x -> Put unserialize :: Serialize x => Get x -- | SPut to FilePath putSPutFile :: FilePath -> SPut -> IO () -- | SGet from FilePath getSGetFile :: FilePath -> SGet a -> IO a -- | Serialize to FilePath putSerializeFile :: Serialize a => FilePath -> a -> IO () -- | Unserialize from FilePath getSerializeFile :: Serialize a => FilePath -> IO a instance Enum SCmd instance (Ord k, Serialize k, Serialize e) => Serialize (Map k e) instance (Ord a, Serialize a) => Serialize (Set a) instance Serialize a => Serialize (Maybe a) instance Serialize a => Serialize [a] instance (Serialize a, Serialize b, Serialize c) => Serialize (a, b, c) instance (Serialize a, Serialize b) => Serialize (a, b) instance Serialize Integer instance Serialize Bool instance Serialize Char instance Serialize Int instance Serialize () instance Binary SCmd module UHC.Util.Pretty type PP_DocL = [PP_Doc] -- | As (>|but doing (-<) when does not fit on single line (>-|-<) :: (PP a, PP b) => a -> b -> PP_Doc -- | As (>#but doing (-<) when does not fit on single line (>-#-<) :: (PP a, PP b) => a -> b -> PP_Doc -- | PP list with open, separator, and close ppListSep :: (PP s, PP c, PP o, PP a) => o -> c -> s -> [a] -> PP_Doc -- | Deprecated: Use pp...Block variants ppListSepV :: (PP s, PP c, PP o, PP a) => o -> c -> s -> [a] -> PP_Doc -- | Deprecated: Use pp...Block variants ppListSepVV :: (PP s, PP c, PP o, PP a) => o -> c -> s -> [a] -> PP_Doc ppCurlys :: PP p => p -> PP_Doc ppPacked :: (PP o, PP c, PP p) => o -> c -> p -> PP_Doc ppPackedWithStrings :: PP p => String -> String -> p -> PP_Doc ppParens :: PP p => p -> PP_Doc ppCurly :: PP p => p -> PP_Doc ppBrackets :: PP p => p -> PP_Doc ppVBar :: PP p => p -> PP_Doc -- | PP list with open, separator, and close in a possibly multiline block -- structure ppBlock :: (PP ocs, PP a) => ocs -> ocs -> ocs -> [a] -> PP_Doc -- | PP list with open, separator, and close in a possibly multiline block -- structure ppBlockH :: (PP ocs, PP a) => ocs -> ocs -> ocs -> [a] -> PP_Doc ppBlock' :: (PP ocs, PP a) => ocs -> ocs -> ocs -> ocs -> [a] -> [PP_Doc] -- | See ppBlock, but with string delimiters aligned properly ppBlockWithStrings :: PP a => String -> String -> String -> [a] -> PP_Doc -- | See ppBlock, but with string delimiters aligned properly, -- yielding a list of elements ppBlockWithStrings' :: PP a => String -> String -> String -> [a] -> [PP_Doc] -- | PP horizontally or vertically with (, ,, and ) in -- a possibly multiline block structure ppParensCommasBlock :: PP a => [a] -> PP_Doc -- | PP horizontally or vertically with {, , and } in -- a possibly multiline block structure ppCurlysBlock :: PP a => [a] -> PP_Doc -- | PP horizontally or vertically with {, ;, and } in -- a possibly multiline block structure ppCurlysSemisBlock :: PP a => [a] -> PP_Doc -- | PP horizontally or vertically with {, ,, and } in -- a possibly multiline block structure ppCurlysCommasBlock :: PP a => [a] -> PP_Doc -- | PP horizontally or vertically with (, ;, and ) in -- a possibly multiline block structure ppParensSemisBlock :: PP a => [a] -> PP_Doc -- | PP horizontally or vertically with [, ,, and ] in -- a possibly multiline block structure ppBracketsCommasBlock :: PP a => [a] -> PP_Doc -- | PP horizontally or vertically with (, ,, and ) in -- a possibly multiline block structure ppParensCommasBlockH :: PP a => [a] -> PP_Doc -- | PP horizontally or vertically with {, , and } in -- a possibly multiline block structure ppCurlysBlockH :: PP a => [a] -> PP_Doc -- | PP horizontally or vertically with {, ;, and } in -- a possibly multiline block structure ppCurlysSemisBlockH :: PP a => [a] -> PP_Doc -- | PP horizontally or vertically with {, ,, and } in -- a possibly multiline block structure ppCurlysCommasBlockH :: PP a => [a] -> PP_Doc -- | PP horizontally or vertically with (, ;, and ) in -- a possibly multiline block structure ppParensSemisBlockH :: PP a => [a] -> PP_Doc -- | PP horizontally or vertically with [, ,, and ] in -- a possibly multiline block structure ppBracketsCommasBlockH :: PP a => [a] -> PP_Doc -- | PP horizontally or vertically with [, ,, and ] in -- a possibly multiline block structure -- | Deprecated: Use ppBracketsCommasBlock ppBracketsCommasV :: PP a => [a] -> PP_Doc -- | Alias for vlist ppVertically :: [PP_Doc] -> PP_Doc -- | PP horizontally: list separated by comma ppCommas :: PP a => [a] -> PP_Doc -- | PP horizontally: list separated by comma + single blank ppCommas' :: PP a => [a] -> PP_Doc -- | PP horizontally: list separated by semicolon ppSemis :: PP a => [a] -> PP_Doc -- | PP horizontally: list separated by semicolon + single blank ppSemis' :: PP a => [a] -> PP_Doc -- | PP horizontally: list separated by single blank ppSpaces :: PP a => [a] -> PP_Doc -- | PP horizontally with {, ,, and } ppCurlysCommas :: PP a => [a] -> PP_Doc -- | PP horizontally with {, , , and } ppCurlysCommas' :: PP a => [a] -> PP_Doc ppCurlysCommasWith :: PP a => (a -> PP_Doc) -> [a] -> PP_Doc -- | PP horizontally with {, ;, and } ppCurlysSemis :: PP a => [a] -> PP_Doc -- | PP horizontally with {, ; , and } ppCurlysSemis' :: PP a => [a] -> PP_Doc -- | PP horizontally with (, , and ) ppParensSpaces :: PP a => [a] -> PP_Doc -- | PP horizontally with (, ,, and ) ppParensCommas :: PP a => [a] -> PP_Doc -- | PP horizontally with (, , , and ) ppParensCommas' :: PP a => [a] -> PP_Doc -- | PP horizontally with [, ,, and ] ppBracketsCommas :: PP a => [a] -> PP_Doc -- | PP horizontally with [, , , and ] ppBracketsCommas' :: PP a => [a] -> PP_Doc -- | Alias for hlist ppHorizontally :: [PP_Doc] -> PP_Doc -- | Deprecated: Use ppListSep ppListSepFill :: (PP s, PP c, PP o, PP a) => o -> c -> s -> [a] -> PP_Doc -- | Only prefix with a Maybe and extra space when Just ppMbPre :: (PP x, PP r) => (a -> x) -> Maybe a -> r -> PP_Doc -- | Only suffix with a Maybe and extra space when Just ppMbPost :: (PP x, PP r) => (a -> x) -> Maybe a -> r -> PP_Doc -- | Only prefix with a list and extra space when non-empty ppListPre :: (PP x, PP r) => ([a] -> x) -> [a] -> r -> PP_Doc -- | Only suffix with a list and extra space when non-empty ppListPost :: (PP x, PP r) => ([a] -> x) -> [a] -> r -> PP_Doc ppDots :: PP a => [a] -> PP_Doc ppMb :: PP a => Maybe a -> PP_Doc -- | Guard around PP: if False pass through ppUnless :: PP x => Bool -> x -> PP_Doc -- | Guard around PP: if True pass through ppWhen :: PP x => Bool -> x -> PP_Doc hPutWidthPPLn :: Handle -> Int -> PP_Doc -> IO () putWidthPPLn :: Int -> PP_Doc -> IO () hPutPPLn :: Handle -> PP_Doc -> IO () putPPLn :: PP_Doc -> IO () hPutPPFile :: Handle -> PP_Doc -> Int -> IO () putPPFile :: String -> PP_Doc -> Int -> IO () putPPFPath :: FPath -> PP_Doc -> Int -> IO () instance (PP a, PP b) => PP (a, b) instance PP Bool instance PP a => PP (Maybe a) module UHC.Util.CompileRun data CompileRunState err CRSOk :: CompileRunState err CRSFail :: CompileRunState err CRSStopSeq :: CompileRunState err CRSStopAllSeq :: CompileRunState err CRSStop :: CompileRunState err CRSFailErrL :: String -> [err] -> (Maybe Int) -> CompileRunState err CRSErrInfoL :: String -> Bool -> [err] -> CompileRunState err data CompileRun nm unit info err CompileRun :: Map nm unit -> [[nm]] -> nm -> CompileRunState err -> info -> CompileRun nm unit info err crCUCache :: CompileRun nm unit info err -> Map nm unit crCompileOrder :: CompileRun nm unit info err -> [[nm]] crTopModNm :: CompileRun nm unit info err -> nm crState :: CompileRun nm unit info err -> CompileRunState err crStateInfo :: CompileRun nm unit info err -> info type CompilePhase n u i e a = StateT (CompileRun n u i e) IO a class CompileUnit u n l s | u -> n l s where cuParticipation _ = [] cuDefault :: CompileUnit u n l s => u cuFPath :: CompileUnit u n l s => u -> FPath cuUpdFPath :: CompileUnit u n l s => FPath -> u -> u cuLocation :: CompileUnit u n l s => u -> l cuUpdLocation :: CompileUnit u n l s => l -> u -> u cuKey :: CompileUnit u n l s => u -> n cuUpdKey :: CompileUnit u n l s => n -> u -> u cuState :: CompileUnit u n l s => u -> s cuUpdState :: CompileUnit u n l s => s -> u -> u cuImports :: CompileUnit u n l s => u -> [n] cuParticipation :: CompileUnit u n l s => u -> [CompileParticipation] class CompileUnitState s cusDefault :: CompileUnitState s => s cusUnk :: CompileUnitState s => s cusIsUnk :: CompileUnitState s => s -> Bool cusIsImpKnown :: CompileUnitState s => s -> Bool class FPathError e => CompileRunError e p | e -> p where crePPErrL _ = empty creMkNotFoundErrL _ _ _ _ = [] creAreFatal _ = True crePPErrL :: CompileRunError e p => [e] -> PP_Doc creMkNotFoundErrL :: CompileRunError e p => p -> String -> [String] -> [FileSuffix] -> [e] creAreFatal :: CompileRunError e p => [e] -> Bool class CompileModName n mkCMNm :: CompileModName n => String -> n class CompileRunStateInfo i n p crsiImportPosOfCUKey :: CompileRunStateInfo i n p => n -> i -> p data CompileParticipation CompileParticipation_NoImport :: CompileParticipation class FileLocatable x loc | loc -> x fileLocation :: FileLocatable x loc => x -> loc noFileLocation :: FileLocatable x loc => loc mkEmptyCompileRun :: n -> i -> CompileRun n u i e crCU :: (Show n, Ord n) => n -> CompileRun n u i e -> u crMbCU :: Ord n => n -> CompileRun n u i e -> Maybe u ppCR :: (PP n, PP u) => CompileRun n u i e -> PP_Doc cpUpdStateInfo :: (i -> i) -> CompilePhase n u i e () cpUpdSI :: (i -> i) -> CompilePhase n u i e () cpUpdCU :: (Ord n, CompileUnit u n l s) => n -> (u -> u) -> CompilePhase n u i e () cpUpdCUWithKey :: (Ord n, CompileUnit u n l s) => n -> (n -> u -> (n, u)) -> CompilePhase n u i e n cpSetFail :: CompilePhase n u i e () cpSetStop :: CompilePhase n u i e () cpSetStopSeq :: CompilePhase n u i e () cpSetStopAllSeq :: CompilePhase n u i e () cpSetOk :: CompilePhase n u i e () cpSetErrs :: [e] -> CompilePhase n u i e () cpSetLimitErrs :: Int -> String -> [e] -> CompilePhase n u i e () cpSetLimitErrsWhen :: Int -> String -> [e] -> CompilePhase n u i e () cpSetInfos :: String -> Bool -> [e] -> CompilePhase n u i e () cpSetCompileOrder :: [[n]] -> CompilePhase n u i e () cpSeq :: CompileRunError e p => [CompilePhase n u i e ()] -> CompilePhase n u i e () cpSeqWhen :: CompileRunError e p => Bool -> [CompilePhase n u i e ()] -> CompilePhase n u i e () cpEmpty :: CompilePhase n u i e () cpFindFileForNameOrFPath :: FPATH n => String -> n -> FPath -> [(String, FPath)] 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] cpFindFilesForFPath :: (Ord n, FPATH n, FileLocatable u String, CompileUnitState s, CompileRunError e p, CompileUnit u n String s, CompileModName n, CompileRunStateInfo i n p) => Bool -> [(FileSuffix, s)] -> [String] -> Maybe n -> Maybe FPath -> CompilePhase n u i e [FPath] cpFindFileForFPath :: (Ord n, FPATH n, FileLocatable u String, CompileUnitState s, CompileRunError e p, CompileUnit u n String s, CompileModName n, CompileRunStateInfo i n p) => [(FileSuffix, s)] -> [String] -> Maybe n -> Maybe FPath -> CompilePhase n u i e (Maybe FPath) -- | Abbreviation for cpImportGatherFromMods for 1 module 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 () -- | recursively extract imported modules 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 () -- | recursively extract imported modules, providing a way to import + do -- the import 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 () cpPP :: (PP n, PP u) => String -> CompilePhase n u i e () cpPPMsg :: PP m => m -> CompilePhase n u i e () forgetM :: Monad m => m a -> m () instance Eq CompileParticipation instance Ord CompileParticipation instance Show (CompileRunState err) instance CompileRunError String () module UHC.Util.PrettyUtils mkTexCmdDef :: (PP cmd, PP a, PP b) => cmd -> a -> b -> PP_Doc mkTexCmdUse :: (PP cmd, PP a) => cmd -> a -> PP_Doc mkTexCmdUse' :: (PP cmd, PP a) => cmd -> a -> PP_Doc module UHC.Util.Debug tr :: Show a1 => [Char] -> a1 -> a -> a trp :: PP b => [Char] -> b -> a -> a module UHC.Util.DependencyGraph data DpdGr n dgTopSort :: DpdGr n -> [n] dgVertices :: Ord n => DpdGr n -> Set n dgReachableFrom :: Ord n => DpdGr n -> n -> Set n dgReachableTo :: Ord n => DpdGr n -> n -> Set n dgDpdsOn :: DpdGr n -> n -> [n] dgIsFirst :: Ord n => DpdGr n -> n -> Set n -> Bool dgCheckSCCMutuals :: (Ord n, PP n) => ([PP_Doc] -> err) -> DpdGr n -> [err] dgSCCToList :: Ord n => DpdGr n -> [[n]] mkDpdGrFromEdges :: Ord n => [(n, [n])] -> DpdGr n mkDpdGrFromEdgesMp :: Ord n => Map n [n] -> DpdGr n mkDpdGrFromEdgesMpPadMissing :: Ord n => Map n [n] -> DpdGr n mkDpdGrFromAssocWithMissing :: Ord n => [n] -> [(n, n)] -> DpdGr n mkDpdGrFromOrderWithMissing :: Ord n => [n] -> [[n]] -> DpdGr n instance PP n => PP (SCC n) instance Show (SCC n) instance (Ord n, PP n) => PP (DpdGr n) instance Show (DpdGr n) module UHC.Util.Nm data Nm' s NmEmp :: Nm' s Nm :: s -> Nm' s nmStr :: Nm' s -> s NmSel :: Nm' s -> Maybe s -> Nm' s nmNm :: Nm' s -> Nm' s nmMbSel :: Nm' s -> Maybe s NmQual :: Nm' s -> s -> Nm' s nmNm :: Nm' s -> Nm' s nmQual :: Nm' s -> s type Nm = Nm' String nmSelSep :: String nmQualSep :: String nmBase' :: Nm -> String nmBase :: Nm -> Nm nmSetSuff :: Nm -> String -> Nm nmSetBase :: Nm -> String -> Nm nmSetSel :: Nm' s -> s -> Nm' s nmSel :: Nm -> String nmInit :: Nm -> Nm nmToMbL :: Nm' s -> [Maybe s] nmToL :: Nm -> [String] nmFromMbL :: [Maybe s] -> Nm' s nmFromL :: [s] -> Nm' s nmApd :: Nm' s -> Nm' s -> Nm' s nmApdL :: [Nm' s] -> Nm' s nmStrApd :: Nm -> Nm -> Nm nmCapitalize :: Nm -> Nm nmDashed :: Nm -> Nm nmFlatten :: Nm -> Nm nmShow' :: String -> Nm -> String nmShowAG :: Nm -> String class NM a mkNm :: NM a => a -> Nm instance Eq s => Eq (Nm' s) instance Ord s => Ord (Nm' s) instance FPATH Nm instance NM Int instance NM String instance NM Nm instance Functor Nm' instance PP Nm instance Show Nm module UHC.Util.ParseErrPrettyPrint ppPos :: Position p => p -> PP_Doc ppErr :: Position pos => (String, pos) -> PP_Doc -> PP_Doc ppWarn :: Position pos => (String, pos) -> PP_Doc -> PP_Doc ppTr :: PP_Doc -> PP_Doc instance (Eq s, Show s, Show p, Position p) => PP (Message s p) module UHC.Util.ScanUtils data ScanOpts ScanOpts :: !(Set String) -> !(Set String) -> !(Set String) -> !(Set String) -> !(Set Char) -> !(Set Char) -> !String -> !(Set Char) -> !(Set String) -> !Bool -> ![String] -> ![String] -> !String -> !String -> !String -> !Bool -> ![(String, String)] -> !Bool -> !Bool -> ScanOpts scoKeywordsTxt :: ScanOpts -> !(Set String) scoPragmasTxt :: ScanOpts -> !(Set String) scoCommandsTxt :: ScanOpts -> !(Set String) scoKeywordsOps :: ScanOpts -> !(Set String) scoKeywExtraChars :: ScanOpts -> !(Set Char) scoSpecChars :: ScanOpts -> !(Set Char) scoStringDelims :: ScanOpts -> !String scoOpChars :: ScanOpts -> !(Set Char) scoSpecPairs :: ScanOpts -> !(Set String) scoDollarIdent :: ScanOpts -> !Bool scoOffsideTrigs :: ScanOpts -> ![String] scoOffsideTrigsGE :: ScanOpts -> ![String] scoOffsideModule :: ScanOpts -> !String scoOffsideOpen :: ScanOpts -> !String scoOffsideClose :: ScanOpts -> !String scoLitmode :: ScanOpts -> !Bool scoVerbOpenClose :: ScanOpts -> ![(String, String)] scoAllowQualified :: ScanOpts -> !Bool scoAllowFloat :: ScanOpts -> !Bool defaultScanOpts :: ScanOpts isNoPos :: Pos -> Bool posIs1stColumn :: Pos -> Bool data InFilePos InFilePos :: Int -> Int -> InFilePos infpLine :: InFilePos -> Int infpColumn :: InFilePos -> Int infpStart :: InFilePos infpNone :: InFilePos infpAdvCol :: Int -> InFilePos -> InFilePos infpAdvLine :: Int -> InFilePos -> InFilePos infpAdv1Line :: InFilePos -> InFilePos infpAdvStr :: String -> InFilePos -> InFilePos genTokVal :: GenToken v t v -> v genTokTp :: GenToken k t v -> Maybe t genTokMap :: (a -> b) -> GenToken a t a -> GenToken b t b isLF :: Char -> Bool isStr :: Char -> Bool isStrQuote :: Char -> Bool isWhite :: Char -> Bool isBlack :: Char -> Bool isVarStart :: Char -> Bool isVarRest :: Char -> Bool instance Eq InFilePos instance Ord InFilePos instance PP Pos instance Position (GenToken k t v) instance Position p => Position (Maybe p) instance Show InFilePos module UHC.Util.AssocL type Assoc k v = (k, v) type AssocL k v = [Assoc k v] assocLMapElt :: (v -> v') -> AssocL k v -> AssocL k v' assocLMapKey :: (k -> k') -> AssocL k v -> AssocL k' v assocLElts :: AssocL k v -> [v] assocLKeys :: AssocL k v -> [k] assocLGroupSort :: Ord k => AssocL k v -> AssocL k [v] assocLMapUnzip :: AssocL k (v1, v2) -> (AssocL k v1, AssocL k v2) ppAssocL :: (PP k, PP v) => AssocL k v -> PP_Doc ppAssocL' :: (PP k, PP v, PP s) => ([PP_Doc] -> PP_Doc) -> s -> AssocL k v -> PP_Doc ppAssocLV :: (PP k, PP v) => AssocL k v -> PP_Doc -- | intended for parsing ppCurlysAssocL :: (k -> PP_Doc) -> (v -> PP_Doc) -> AssocL k v -> PP_Doc -- | A VarMp maps from variables (tvars, ...) to whatever else has to be -- mapped to (Ty, ...). -- -- Starting with variant 6 (which introduces kinds) it allows multiple -- meta level mapping, in that the VarMp holds mappings for multiple meta -- levels. This allows one map to both map to base level info and to -- higher levels. In particular this is used by fitsIn which also -- instantiates types, and types may quantify over type variables with -- other kinds than kind *, which must be propagated. A separate map -- could have been used, but this holds the info together and is -- extendible to more levels. -- -- A multiple level VarMp knows its own absolute metalevel, which is the -- default to use for lookup. module UHC.Util.VarMp data VarMp' k v VarMp :: !MetaLev -> [Map k v] -> VarMp' k v -- | the base meta level varmpMetaLev :: VarMp' k v -> !MetaLev -- | for each level a map, starting at the base meta level varmpMpL :: VarMp' k v -> [Map k v] ppVarMpV :: (PP k, PP v) => VarMp' k v -> PP_Doc varmpFilter :: Ord k => (k -> v -> Bool) -> VarMp' k v -> VarMp' k v -- | Delete varmpDel :: Ord k => [k] -> VarMp' k v -> VarMp' k v (|\>) :: Ord k => VarMp' k v -> [k] -> VarMp' k v -- | Alter irrespective of level varmpAlter :: Ord k => (Maybe v -> Maybe v) -> k -> VarMp' k v -> VarMp' k v varmpUnion :: Ord k => VarMp' k v -> VarMp' k v -> VarMp' k v varmpUnions :: Ord k => [VarMp' k v] -> VarMp' k v mkVarMp :: Map k v -> VarMp' k v emptyVarMp :: VarMp' k v varmpIsEmpty :: VarMp' k v -> Bool varmpShiftMetaLev :: MetaLev -> VarMp' k v -> VarMp' k v varmpIncMetaLev :: VarMp' k v -> VarMp' k v varmpDecMetaLev :: VarMp' k v -> VarMp' k v varmpSelectMetaLev :: [MetaLev] -> VarMp' k v -> VarMp' k v varmpKeys :: Ord k => VarMp' k v -> [k] varmpKeysSet :: Ord k => VarMp' k v -> Set k varmpMetaLevSingleton :: MetaLev -> k -> v -> VarMp' k v varmpSingleton :: k -> v -> VarMp' k v assocMetaLevLToVarMp :: Ord k => AssocL k (MetaLev, v) -> VarMp' k v assocLToVarMp :: Ord k => AssocL k v -> VarMp' k v varmpToAssocL :: VarMp' k i -> AssocL k i varmpPlus :: Ord k => VarMp' k v -> VarMp' k v -> VarMp' k v -- | combine by taking the lowest level, adapting the lists with maps -- accordingly varmpUnionWith :: Ord k => (v -> v -> v) -> VarMp' k v -> VarMp' k v -> VarMp' k v varmpLookup :: (VarLookup m k i, Ord k) => k -> m -> Maybe i ppVarMp :: (PP k, PP v) => ([PP_Doc] -> PP_Doc) -> VarMp' k v -> PP_Doc -- | Extract first level map, together with a construction function putting -- a new map into the place of the previous one varmpAsMap :: VarMp' k v -> (Map k v, Map k v -> VarMp' k v) varmpMapMaybe :: Ord k => (a -> Maybe b) -> VarMp' k a -> VarMp' k b varmpMap :: Ord k => (a -> b) -> VarMp' k a -> VarMp' k b varmpInsertWith :: Ord k => (v -> v -> v) -> k -> v -> VarMp' k v -> VarMp' k v data VarMpStk' k v emptyVarMpStk :: VarMpStk' k v varmpstkUnit :: Ord k => k -> v -> VarMpStk' k v varmpstkPushEmpty :: VarMpStk' k v -> VarMpStk' k v varmpstkPop :: VarMpStk' k v -> (VarMpStk' k v, VarMpStk' k v) varmpstkToAssocL :: VarMpStk' k v -> AssocL k v varmpstkKeysSet :: Ord k => VarMpStk' k v -> Set k varmpstkUnions :: Ord k => [VarMpStk' k v] -> VarMpStk' k v varmpSize :: VarMp' k v -> Int varmpToMap :: VarMp' k v -> Map k v instance [overlap ok] Typeable2 VarMp' instance [overlap ok] (Eq k, Eq v) => Eq (VarMp' k v) instance [overlap ok] (Ord k, Ord v) => Ord (VarMp' k v) instance [overlap ok] (Data k, Data v, Ord k) => Data (VarMp' k v) instance [overlap ok] Show (VarMpStk' k v) instance [overlap ok] (Ord k, Serialize k, Serialize v) => Serialize (VarMp' k v) instance [overlap ok] (PP k, PP v) => PP (VarMpStk' k v) instance [overlap ok] (PP k, PP v) => PP (VarMp' k v) instance [overlap ok] Ord k => VarLookupCmb (VarMpStk' k v) (VarMpStk' k v) instance [overlap ok] Ord k => VarLookup (VarMpStk' k v) k v instance [overlap ok] Show (VarMp' k v) instance [overlap ok] Ord k => VarLookupCmb (VarMp' k v) (VarMp' k v) instance [overlap ok] Ord k => VarLookup (VarMp' k v) k v instance [overlap ok] VarLookupBase (VarMp' k v) k v -- | Environment/Gamma where the lexical level + scoping is used to provide -- nesting behavior. Both a SGam and its entries know at which scope they -- are. -- -- Insertion is efficient, lookup also, because a single Map is used. -- -- The Map holds multiple entries, each with its own scope identifier. An -- SGam holds - a stack of scopes, encoding the nesting, where - each -- scope holds mappings for MetaLev's -- -- Results are filtered out w.r.t. this stack, i.e. are checked to be in -- scope. In principle this can be done eagerly, that is, immediately -- after a change in scope, in particular in sgamPop. After some -- experimentation it did turn out that doing this lazily is overall -- faster, that is, when the SGam is consulted (lookup, conversion to -- association list, etc). Conceptually thus the invariant is that no -- entry is in the map which is not in scope. Guaranteeing this invariant -- is thus not done by the one function breaking it (sgamPop). module UHC.Util.ScopeMapGam data SGam k v emptySGam :: SGam k v -- | do it all: map, filter, fold sgamFilterMapEltAccumWithKey :: Ord k' => (k -> SGamElt v -> Bool) -> (k -> SGamElt v -> acc -> (k', SGamElt v', acc)) -> (k -> SGamElt v -> acc -> acc) -> acc -> SGam k v -> (SGam k' v', acc) sgamMapEltWithKey :: (Ord k, Ord k') => (k -> SGamElt v -> (k', SGamElt v')) -> SGam k v -> SGam k' v' sgamMapThr :: (Ord k, Ord k') => ((k, v) -> t -> ((k', v'), t)) -> t -> SGam k v -> (SGam k' v', t) sgamMap :: (Ord k, Ord k') => ((k, v) -> (k', v')) -> SGam k v -> SGam k' v' -- | split gam in top and the rest, both with the same scope sgamPop :: Ord k => SGam k v -> (SGam k v, SGam k v) -- | top gam, with same scope as g sgamTop :: Ord k => SGam k v -> SGam k v -- | enter a new scope sgamPushNew :: SGam k v -> SGam k v -- | enter a new scope, add g1 in that scope to g2 sgamPushGam :: Ord k => SGam k v -> SGam k v -> SGam k v -- | Construct singleton gam, on a particular meta level sgamMetaLevSingleton :: MetaLev -> k -> v -> SGam k v -- | Construct singleton gam sgamSingleton :: k -> v -> SGam k v -- | combine gam, g1 is added to g2 with scope of g2 sgamUnionWith :: Ord k => Maybe (v -> [v] -> [v]) -> SGam k v -> SGam k v -> SGam k v sgamUnion :: Ord k => SGam k v -> SGam k v -> SGam k v -- | equivalent of partition sgamPartitionEltWithKey :: Ord k => (k -> SGamElt v -> Bool) -> SGam k v -> (SGam k v, SGam k v) sgamPartitionWithKey :: Ord k => (k -> v -> Bool) -> SGam k v -> (SGam k v, SGam k v) -- | equivalent of unzip sgamUnzip :: Ord k => SGam k (v1, v2) -> (SGam k v1, SGam k v2) -- | Alter on top of the scope stack, including all duplicates sgamAlterDupOnTop :: Ord k => (Maybe v -> Maybe v) -> k -> SGam k v -> SGam k v -- | lookup, return at least one found value, otherwise Nothing sgamLookupMetaLevDup :: Ord k => MetaLev -> k -> SGam k v -> Maybe [v] -- | convert to association list, with all duplicates, scope is lost sgamToAssocDupL :: Ord k => SGam k v -> AssocL k [v] -- | convert from association list, assume default scope sgamFromAssocDupL :: Ord k => AssocL k [v] -> SGam k v -- | get rid of duplicate entries, by taking the first of them all sgamNoDups :: Ord k => SGam k v -> SGam k v -- | Level to lookup into type MetaLev = Int -- | Base level (of values, usually) metaLevVal :: MetaLev instance Typeable1 SGamElt instance Typeable2 SGam instance Data v => Data (SGamElt v) instance (Data k, Data v, Ord k) => Data (SGam k v) instance (Ord k, Serialize k, Serialize v) => Serialize (SGam k v) instance Serialize v => Serialize (SGamElt v) instance Show (SGam k v) module UHC.Util.AGraph data AGraph a b insertEdge :: Ord a => (a, a, b) -> AGraph a b -> AGraph a b insertEdges :: Ord a => [(a, a, b)] -> AGraph a b -> AGraph a b deleteEdge :: Ord a => (a, a) -> AGraph a b -> AGraph a b deleteNode :: Ord a => a -> AGraph a b -> AGraph a b successors :: Ord a => AGraph a b -> a -> [(b, a)] predecessors :: Ord a => AGraph a b -> a -> [(b, a)] emptyAGraph :: Ord a => AGraph a b instance (Show a, Show b) => Show (AGraph a b)