Skip to content

Commit

Permalink
Add Foldable & Traversable Field instances
Browse files Browse the repository at this point in the history
  • Loading branch information
phadej committed Apr 1, 2019
1 parent a21ae5e commit 27cf519
Showing 1 changed file with 6 additions and 4 deletions.
10 changes: 6 additions & 4 deletions Cabal/Distribution/Fields/Field.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,6 @@
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveTraversable #-}
-- | Cabal-like file AST types: 'Field', 'Section' etc
--
-- These types are parametrized by an annotation.
Expand Down Expand Up @@ -33,7 +35,7 @@ import qualified Data.Char as Char
data Field ann
= Field !(Name ann) [FieldLine ann]
| Section !(Name ann) [SectionArg ann] [Field ann]
deriving (Eq, Show, Functor)
deriving (Eq, Show, Functor, Foldable, Traversable)

-- | Section of field name
fieldName :: Field ann -> Name ann
Expand All @@ -56,7 +58,7 @@ fieldUniverse f@(Field _ _) = [f]
--
-- /Invariant:/ 'ByteString' has no newlines.
data FieldLine ann = FieldLine !ann !ByteString
deriving (Eq, Show, Functor)
deriving (Eq, Show, Functor, Foldable, Traversable)

-- | Section arguments, e.g. name of the library
data SectionArg ann
Expand All @@ -66,7 +68,7 @@ data SectionArg ann
-- ^ quoted string
| SecArgOther !ann !ByteString
-- ^ everything else, mm. operators (e.g. in if-section conditionals)
deriving (Eq, Show, Functor)
deriving (Eq, Show, Functor, Foldable, Traversable)

-- | Extract annotation from 'SectionArg'.
sectionArgAnn :: SectionArg ann -> ann
Expand All @@ -84,7 +86,7 @@ type FieldName = ByteString
--
-- /Invariant/: 'ByteString' is lower-case ASCII.
data Name ann = Name !ann !FieldName
deriving (Eq, Show, Functor)
deriving (Eq, Show, Functor, Foldable, Traversable)

mkName :: ann -> FieldName -> Name ann
mkName ann bs = Name ann (B.map Char.toLower bs)
Expand Down

0 comments on commit 27cf519

Please sign in to comment.