Skip to content
Snippets Groups Projects
Commit 27cf519a authored by Oleg Grenrus's avatar Oleg Grenrus
Browse files

Add Foldable & Traversable Field instances

parent a21ae5e3
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveTraversable #-}
-- | Cabal-like file AST types: 'Field', 'Section' etc
--
-- These types are parametrized by an annotation.
......@@ -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
......@@ -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
......@@ -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
......@@ -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)
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment