Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data JSModuleStyle
- data Doc
- minifiedCodeLinesLength :: Int
- render :: Bool -> Doc -> String
- ($+$) :: Doc -> Doc -> Doc
- ($++$) :: Doc -> Doc -> Doc
- (<+>) :: Doc -> Doc -> Doc
- text :: String -> Doc
- group :: Doc -> Doc
- indentBy :: Int -> Doc -> Doc
- enclose :: Doc -> Doc -> Doc -> Doc
- space :: Doc
- indent :: Doc -> Doc
- hcat :: [Doc] -> Doc
- vcat :: [Doc] -> Doc
- vsep :: [Doc] -> Doc
- punctuate :: Doc -> [Doc] -> Doc
- parens :: Doc -> Doc
- brackets :: Doc -> Doc
- braces :: Doc -> Doc
- mparens :: Bool -> Doc -> Doc
- unescape :: Char -> String
- unescapes :: String -> Doc
- class Pretty a where
- pretty :: (Nat, Bool, JSModuleStyle) -> a -> Doc
- prettyShow :: Pretty a => Bool -> JSModuleStyle -> a -> String
- class Pretties a where
- pretties :: (Nat, Bool, JSModuleStyle) -> a -> [Doc]
- block :: (Nat, Bool, JSModuleStyle) -> Exp -> Doc
- modname :: GlobalId -> Doc
- exports :: (Nat, Bool, JSModuleStyle) -> Set JSQName -> [Export] -> Doc
- variableName :: String -> String
- isValidJSIdent :: String -> Bool
Documentation
data JSModuleStyle Source #
Instances
NFData JSModuleStyle | |||||
Defined in Agda.Compiler.JS.Compiler rnf :: JSModuleStyle -> () | |||||
Generic JSModuleStyle Source # | |||||
Defined in Agda.Compiler.JS.Pretty
from :: JSModuleStyle -> Rep JSModuleStyle x to :: Rep JSModuleStyle x -> JSModuleStyle | |||||
type Rep JSModuleStyle Source # | |||||
Defined in Agda.Compiler.JS.Pretty type Rep JSModuleStyle = D1 ('MetaData "JSModuleStyle" "Agda.Compiler.JS.Pretty" "Agda-2.6.20240714-inplace" 'False) (C1 ('MetaCons "JSCJS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "JSAMD" 'PrefixI 'False) (U1 :: Type -> Type)) |
minifiedCodeLinesLength :: Int Source #
(<+>) :: Doc -> Doc -> Doc infixr 6 Source #
Separate by space that will be removed by minify.
For non-removable space, use d <> " " <> d'
.
Instances
Pretty Comment Source # | |
Defined in Agda.Compiler.JS.Pretty | |
Pretty Exp Source # | |
Defined in Agda.Compiler.JS.Pretty | |
Pretty GlobalId Source # | |
Defined in Agda.Compiler.JS.Pretty | |
Pretty LocalId Source # | |
Defined in Agda.Compiler.JS.Pretty | |
Pretty MemberId Source # | |
Defined in Agda.Compiler.JS.Pretty | |
Pretty Module Source # | |
Defined in Agda.Compiler.JS.Pretty | |
Pretty a => Pretty (Maybe a) Source # | |
Defined in Agda.Compiler.JS.Pretty | |
Pretty [(GlobalId, Export)] Source # | |
Defined in Agda.Compiler.JS.Pretty | |
(Pretty a, Pretty b) => Pretty (a, b) Source # | |
Defined in Agda.Compiler.JS.Pretty |
prettyShow :: Pretty a => Bool -> JSModuleStyle -> a -> String Source #
variableName :: String -> String Source #
isValidJSIdent :: String -> Bool Source #
Check if a string is a valid JS identifier. The check ignores keywords as we prepend z_ to our identifiers. The check is conservative and may not admit all valid JS identifiers.