| Safe Haskell | Safe-Inferred |
|---|---|
| Language | GHC2021 |
Hix.Preproc
Documentation
type Regex = IndexedTraversal' Int ByteString Match Source #
data CabalConfig Source #
Constructors
| CabalConfig | |
Fields
| |
Instances
| Generic CabalConfig Source # | |
Defined in Hix.Preproc Associated Types type Rep CabalConfig :: Type -> Type # | |
| Show CabalConfig Source # | |
Defined in Hix.Preproc Methods showsPrec :: Int -> CabalConfig -> ShowS # show :: CabalConfig -> String # showList :: [CabalConfig] -> ShowS # | |
| type Rep CabalConfig Source # | |
Defined in Hix.Preproc type Rep CabalConfig = D1 ('MetaData "CabalConfig" "Hix.Preproc" "hix-0.5.8-3pbth8EbMLYAAF7nZjOA0q" 'False) (C1 ('MetaCons "CabalConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "extensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Builder]) :*: (S1 ('MetaSel ('Just "ghcOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Builder]) :*: S1 ('MetaSel ('Just "prelude") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Prelude))))) | |
newtype DummyExportName Source #
Constructors
| DummyExportName | |
Fields | |
Instances
takeLine :: ByteString -> Maybe (ByteString, ByteString) Source #
line :: ByteString -> Builder Source #
joinLinesReverse :: [ByteString] -> ByteString Source #
joinLinesReverseBuilder :: [ByteString] -> Builder Source #
languagePragma :: [Builder] -> Builder Source #
optionsPragma :: Builder -> Builder Source #
commentRegex :: Regex Source #
moduleRegex :: Regex Source #
importRegex :: Regex Source #
isComment :: ByteString -> Bool Source #
isModule :: ByteString -> Maybe ByteString Source #
isModuleEnd :: ByteString -> Bool Source #
isImportsEnd :: ByteString -> Bool Source #
isImport :: ByteString -> Bool Source #
Constructors
| PreModule | |
| ModuleStart | |
| ModuleExports | |
| Imports |
Instances
| Generic Phase Source # | |
| Show Phase Source # | |
| Eq Phase Source # | |
| type Rep Phase Source # | |
Defined in Hix.Preproc type Rep Phase = D1 ('MetaData "Phase" "Hix.Preproc" "hix-0.5.8-3pbth8EbMLYAAF7nZjOA0q" 'False) ((C1 ('MetaCons "PreModule" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ModuleStart" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ModuleExports" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Imports" 'PrefixI 'False) (U1 :: Type -> Type))) | |
data PreludeAction Source #
Constructors
| PreludeDefault | |
| PreludeNoImplicit | |
| PreludeReplaced |
Instances
| Generic PreludeAction Source # | |
Defined in Hix.Preproc Associated Types type Rep PreludeAction :: Type -> Type # | |
| Show PreludeAction Source # | |
Defined in Hix.Preproc Methods showsPrec :: Int -> PreludeAction -> ShowS # show :: PreludeAction -> String # showList :: [PreludeAction] -> ShowS # | |
| Eq PreludeAction Source # | |
Defined in Hix.Preproc Methods (==) :: PreludeAction -> PreludeAction -> Bool # (/=) :: PreludeAction -> PreludeAction -> Bool # | |
| type Rep PreludeAction Source # | |
Defined in Hix.Preproc type Rep PreludeAction = D1 ('MetaData "PreludeAction" "Hix.Preproc" "hix-0.5.8-3pbth8EbMLYAAF7nZjOA0q" 'False) (C1 ('MetaCons "PreludeDefault" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PreludeNoImplicit" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PreludeReplaced" 'PrefixI 'False) (U1 :: Type -> Type))) | |
data CustomPrelude Source #
Constructors
| CustomPrelude Prelude PreludeAction | |
| NoCustomPrelude |
Instances
| Generic CustomPrelude Source # | |
Defined in Hix.Preproc Associated Types type Rep CustomPrelude :: Type -> Type # | |
| Show CustomPrelude Source # | |
Defined in Hix.Preproc Methods showsPrec :: Int -> CustomPrelude -> ShowS # show :: CustomPrelude -> String # showList :: [CustomPrelude] -> ShowS # | |
| type Rep CustomPrelude Source # | |
Defined in Hix.Preproc type Rep CustomPrelude = D1 ('MetaData "CustomPrelude" "Hix.Preproc" "hix-0.5.8-3pbth8EbMLYAAF7nZjOA0q" 'False) (C1 ('MetaCons "CustomPrelude" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Prelude) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PreludeAction)) :+: C1 ('MetaCons "NoCustomPrelude" 'PrefixI 'False) (U1 :: Type -> Type)) | |
preludeRegex :: Regex Source #
replacePrelude :: ByteString -> Prelude -> Maybe ByteString Source #
parenRegex :: Regex Source #
insertExport :: ByteString -> ByteString Source #
moduleExports :: ByteString -> [ByteString] Source #
Constructors
| Header | |
Fields
| |
Instances
Constructors
| ScanState | |
Fields
| |
Instances
scanHeader :: Maybe Prelude -> ByteString -> Header Source #
customPreludeImport :: Prelude -> Builder Source #
pattern NeedPreludeExtensions :: PreludeAction Source #
needDummy :: CustomPrelude -> Bool Source #
pattern NeedDummy :: CustomPrelude Source #
explicitPreludeImport :: Builder -> CustomPrelude -> Builder Source #
dummyDecl :: CustomPrelude -> Builder -> DummyExportName -> Builder Source #
replaceDummy :: CustomPrelude -> Bool -> DummyExportName -> ByteString -> ByteString Source #
assemble :: Path Abs File -> Header -> Maybe Builder -> Maybe Builder -> DummyExportName -> Builder Source #
preprocessModule :: Path Abs File -> CabalConfig -> DummyExportName -> ByteString -> Builder Source #
preprocessWith :: PreprocOptions -> CabalConfig -> M () Source #
fromConfig :: Maybe (Path Abs Dir) -> Path Abs File -> Either PreprocConfig JsonConfig -> M CabalConfig Source #
fromCabal :: BuildInfo -> CabalConfig Source #
fromCabalFile :: Path Abs File -> M CabalConfig Source #
preprocess :: PreprocOptions -> M () Source #