Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Field ann
- fieldName :: Field ann -> Name ann
- fieldAnn :: Field ann -> ann
- fieldUniverse :: Field ann -> [Field ann]
- data FieldLine ann = FieldLine !ann !ByteString
- fieldLineAnn :: FieldLine ann -> ann
- fieldLineBS :: FieldLine ann -> ByteString
- data SectionArg ann
- = SecArgName !ann !ByteString
- | SecArgStr !ann !ByteString
- | SecArgOther !ann !ByteString
- sectionArgAnn :: SectionArg ann -> ann
- type FieldName = ByteString
- data Name ann = Name !ann !FieldName
- mkName :: ann -> FieldName -> Name ann
- getName :: Name ann -> FieldName
- nameAnn :: Name ann -> ann
Cabal file
A Cabal-like file consists of a series of fields (foo: bar
) and sections (library ...
).
Instances
Functor Field # | |
Foldable Field # | |
Defined in Distribution.Fields.Field fold :: Monoid m => Field m -> m Source # foldMap :: Monoid m => (a -> m) -> Field a -> m Source # foldMap' :: Monoid m => (a -> m) -> Field a -> m Source # foldr :: (a -> b -> b) -> b -> Field a -> b Source # foldr' :: (a -> b -> b) -> b -> Field a -> b Source # foldl :: (b -> a -> b) -> b -> Field a -> b Source # foldl' :: (b -> a -> b) -> b -> Field a -> b Source # foldr1 :: (a -> a -> a) -> Field a -> a Source # foldl1 :: (a -> a -> a) -> Field a -> a Source # toList :: Field a -> [a] Source # null :: Field a -> Bool Source # length :: Field a -> Int Source # elem :: Eq a => a -> Field a -> Bool Source # maximum :: Ord a => Field a -> a Source # minimum :: Ord a => Field a -> a Source # | |
Traversable Field # | |
Eq ann => Eq (Field ann) # | |
Show ann => Show (Field ann) # | |
fieldUniverse :: Field ann -> [Field ann] Source #
All transitive descendants of Field
, including itself.
Note: the resulting list is never empty.
A line of text representing the value of a field from a Cabal file. A field may contain multiple lines.
Invariant: ByteString
has no newlines.
FieldLine !ann !ByteString |
Instances
Functor FieldLine # | |
Foldable FieldLine # | |
Defined in Distribution.Fields.Field fold :: Monoid m => FieldLine m -> m Source # foldMap :: Monoid m => (a -> m) -> FieldLine a -> m Source # foldMap' :: Monoid m => (a -> m) -> FieldLine a -> m Source # foldr :: (a -> b -> b) -> b -> FieldLine a -> b Source # foldr' :: (a -> b -> b) -> b -> FieldLine a -> b Source # foldl :: (b -> a -> b) -> b -> FieldLine a -> b Source # foldl' :: (b -> a -> b) -> b -> FieldLine a -> b Source # foldr1 :: (a -> a -> a) -> FieldLine a -> a Source # foldl1 :: (a -> a -> a) -> FieldLine a -> a Source # toList :: FieldLine a -> [a] Source # null :: FieldLine a -> Bool Source # length :: FieldLine a -> Int Source # elem :: Eq a => a -> FieldLine a -> Bool Source # maximum :: Ord a => FieldLine a -> a Source # minimum :: Ord a => FieldLine a -> a Source # | |
Traversable FieldLine # | |
Defined in Distribution.Fields.Field | |
Eq ann => Eq (FieldLine ann) # | |
Show ann => Show (FieldLine ann) # | |
fieldLineAnn :: FieldLine ann -> ann Source #
Since: Cabal-3.0.0.0
fieldLineBS :: FieldLine ann -> ByteString Source #
Since: Cabal-3.0.0.0
data SectionArg ann Source #
Section arguments, e.g. name of the library
SecArgName !ann !ByteString | identifier, or something which looks like number. Also many dot numbers, i.e. "7.6.3" |
SecArgStr !ann !ByteString | quoted string |
SecArgOther !ann !ByteString | everything else, mm. operators (e.g. in if-section conditionals) |
Instances
sectionArgAnn :: SectionArg ann -> ann Source #
Extract annotation from SectionArg
.
Name
type FieldName = ByteString Source #
A field name.
Invariant: ByteString
is lower-case ASCII.
Instances
Functor Name # | |
Foldable Name # | |
Defined in Distribution.Fields.Field fold :: Monoid m => Name m -> m Source # foldMap :: Monoid m => (a -> m) -> Name a -> m Source # foldMap' :: Monoid m => (a -> m) -> Name a -> m Source # foldr :: (a -> b -> b) -> b -> Name a -> b Source # foldr' :: (a -> b -> b) -> b -> Name a -> b Source # foldl :: (b -> a -> b) -> b -> Name a -> b Source # foldl' :: (b -> a -> b) -> b -> Name a -> b Source # foldr1 :: (a -> a -> a) -> Name a -> a Source # foldl1 :: (a -> a -> a) -> Name a -> a Source # toList :: Name a -> [a] Source # null :: Name a -> Bool Source # length :: Name a -> Int Source # elem :: Eq a => a -> Name a -> Bool Source # maximum :: Ord a => Name a -> a Source # minimum :: Ord a => Name a -> a Source # | |
Traversable Name # | |
Eq ann => Eq (Name ann) # | |
Show ann => Show (Name ann) # | |