| Copyright | (c) 2025 Sam S. Almahri |
|---|---|
| License | MIT |
| Maintainer | [email protected] |
| Safe Haskell | None |
| Language | Haskell2010 |
Web.Todoist.Domain.Section
Description
This module provides types and operations for working with Todoist sections. Sections are used to organize tasks within a project into logical groups.
Usage Example
import Web.Todoist.Domain.Section
import Web.Todoist.Runner
import Web.Todoist.Util.Builder
main :: IO ()
main = do
let config = newTodoistConfig "your-api-token"
-- Create a section in a project
let newSec = runBuilder (newSectionBuilder "To Do" "project-id-123") mempty
section <- todoist config (addSection newSec)
-- Get all sections in a project with builder pattern
let params = runBuilder sectionParamBuilder (withProjectId "project-id-123" <> withLimit 50)
sections <- todoist config (getSections params)
For more details, see: https://developer.todoist.com/rest/v2/#sections
Synopsis
- data Section = Section {
- _id :: SectionId
- _name :: Name
- _project_id :: ProjectId
- _is_collapsed :: IsCollapsed
- _order :: Order
- newtype SectionId = SectionId {}
- data SectionCreate
- data SectionUpdate
- data SectionParam = SectionParam {}
- class Monad m => TodoistSectionM (m :: Type -> Type) where
- getSections :: SectionParam -> m [Section]
- getSection :: SectionId -> m Section
- addSection :: SectionCreate -> m SectionId
- updateSection :: SectionUpdate -> SectionId -> m Section
- deleteSection :: SectionId -> m ()
- getSectionsPaginated :: SectionParam -> m ([Section], Maybe Text)
- newSectionBuilder :: Text -> Text -> Initial SectionCreate
- updateSectionBuilder :: Initial SectionUpdate
- sectionParamBuilder :: Initial SectionParam
- sectionId :: Getter Section SectionId
- sectionName :: Getter Section Name
- sectionProjectId :: Getter Section ProjectId
- sectionIsCollapsed :: Getter Section IsCollapsed
- sectionOrder :: Getter Section Order
Types
Simplified domain representation of a Section (5 essential fields) Note: API returns 11 fields, but we only expose the essential ones
Constructors
| Section | |
Fields
| |
Instances
Unique identifier for a Section
Instances
| FromJSON SectionId Source # | |||||
Defined in Web.Todoist.Domain.Section | |||||
| ToJSON SectionId Source # | |||||
| Generic SectionId Source # | |||||
Defined in Web.Todoist.Domain.Section Associated Types
| |||||
| Show SectionId Source # | |||||
| Eq SectionId Source # | |||||
| type Rep SectionId Source # | |||||
Defined in Web.Todoist.Domain.Section | |||||
data SectionCreate Source #
Request body for creating a new Section
Instances
| ToJSON SectionCreate Source # | |||||
Defined in Web.Todoist.Domain.Section Methods toJSON :: SectionCreate -> Value # toEncoding :: SectionCreate -> Encoding # toJSONList :: [SectionCreate] -> Value # toEncodingList :: [SectionCreate] -> Encoding # omitField :: SectionCreate -> Bool # | |||||
| Generic SectionCreate Source # | |||||
Defined in Web.Todoist.Domain.Section Associated Types
| |||||
| Show SectionCreate Source # | |||||
Defined in Web.Todoist.Domain.Section Methods showsPrec :: Int -> SectionCreate -> ShowS # show :: SectionCreate -> String # showList :: [SectionCreate] -> ShowS # | |||||
| HasName SectionCreate Source # | |||||
Defined in Web.Todoist.Domain.Section Methods hasName :: Text -> SectionCreate -> SectionCreate Source # | |||||
| HasOrder SectionCreate Source # | |||||
Defined in Web.Todoist.Domain.Section Methods hasOrder :: Int -> SectionCreate -> SectionCreate Source # | |||||
| type Rep SectionCreate Source # | |||||
Defined in Web.Todoist.Domain.Section type Rep SectionCreate = D1 ('MetaData "SectionCreate" "Web.Todoist.Domain.Section" "todoist-sdk-0.1.2.1-DGBtxdXKO1e8ZQYcxjFTC8" 'False) (C1 ('MetaCons "SectionCreate" 'PrefixI 'True) (S1 ('MetaSel ('Just "_name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Just "_project_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProjectId) :*: S1 ('MetaSel ('Just "_order") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Order))))) | |||||
data SectionUpdate Source #
Request body for updating a Section (partial updates) Uses omitNothingFields to only send fields that are set
Instances
| ToJSON SectionUpdate Source # | |||||
Defined in Web.Todoist.Domain.Section Methods toJSON :: SectionUpdate -> Value # toEncoding :: SectionUpdate -> Encoding # toJSONList :: [SectionUpdate] -> Value # toEncodingList :: [SectionUpdate] -> Encoding # omitField :: SectionUpdate -> Bool # | |||||
| Generic SectionUpdate Source # | |||||
Defined in Web.Todoist.Domain.Section Associated Types
| |||||
| Show SectionUpdate Source # | |||||
Defined in Web.Todoist.Domain.Section Methods showsPrec :: Int -> SectionUpdate -> ShowS # show :: SectionUpdate -> String # showList :: [SectionUpdate] -> ShowS # | |||||
| HasName SectionUpdate Source # | |||||
Defined in Web.Todoist.Domain.Section Methods hasName :: Text -> SectionUpdate -> SectionUpdate Source # | |||||
| type Rep SectionUpdate Source # | |||||
Defined in Web.Todoist.Domain.Section type Rep SectionUpdate = D1 ('MetaData "SectionUpdate" "Web.Todoist.Domain.Section" "todoist-sdk-0.1.2.1-DGBtxdXKO1e8ZQYcxjFTC8" 'True) (C1 ('MetaCons "SectionUpdate" 'PrefixI 'True) (S1 ('MetaSel ('Just "_name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Name)))) | |||||
data SectionParam Source #
Query parameters for filtering and paginating sections
Constructors
| SectionParam | |
Instances
| Generic SectionParam Source # | |||||
Defined in Web.Todoist.Domain.Section Associated Types
| |||||
| Show SectionParam Source # | |||||
Defined in Web.Todoist.Domain.Section Methods showsPrec :: Int -> SectionParam -> ShowS # show :: SectionParam -> String # showList :: [SectionParam] -> ShowS # | |||||
| HasCursor SectionParam Source # | |||||
Defined in Web.Todoist.Domain.Section Methods hasCursor :: Text -> SectionParam -> SectionParam Source # | |||||
| HasLimit SectionParam Source # | |||||
Defined in Web.Todoist.Domain.Section Methods hasLimit :: Int -> SectionParam -> SectionParam Source # | |||||
| HasProjectId SectionParam Source # | |||||
Defined in Web.Todoist.Domain.Section Methods hasProjectId :: Text -> SectionParam -> SectionParam Source # | |||||
| QueryParam SectionParam Source # | |||||
Defined in Web.Todoist.Domain.Section Methods toQueryParam :: SectionParam -> Params Source # | |||||
| type Rep SectionParam Source # | |||||
Defined in Web.Todoist.Domain.Section type Rep SectionParam = D1 ('MetaData "SectionParam" "Web.Todoist.Domain.Section" "todoist-sdk-0.1.2.1-DGBtxdXKO1e8ZQYcxjFTC8" 'False) (C1 ('MetaCons "SectionParam" 'PrefixI 'True) (S1 ('MetaSel ('Just "project_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ProjectId)) :*: (S1 ('MetaSel ('Just "cursor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "limit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))) | |||||
Type Class
class Monad m => TodoistSectionM (m :: Type -> Type) where Source #
Type class defining Section operations
Methods
getSections :: SectionParam -> m [Section] Source #
Get all sections (automatically fetches all pages)
getSection :: SectionId -> m Section Source #
Get a single section by ID
addSection :: SectionCreate -> m SectionId Source #
Create a new section
updateSection :: SectionUpdate -> SectionId -> m Section Source #
Update a section
deleteSection :: SectionId -> m () Source #
Delete a section (and all its tasks)
getSectionsPaginated :: SectionParam -> m ([Section], Maybe Text) Source #
Get sections with manual pagination control Returns a tuple of (results, next_cursor) for the requested page
Instances
| TodoistSectionM TodoistIO Source # | |
Defined in Web.Todoist.Runner.IO.Interpreters Methods getSections :: SectionParam -> TodoistIO [Section] Source # getSection :: SectionId -> TodoistIO Section Source # addSection :: SectionCreate -> TodoistIO SectionId Source # updateSection :: SectionUpdate -> SectionId -> TodoistIO Section Source # deleteSection :: SectionId -> TodoistIO () Source # getSectionsPaginated :: SectionParam -> TodoistIO ([Section], Maybe Text) Source # | |
| TodoistSectionM Trace Source # | |
Defined in Web.Todoist.Runner.Trace Methods getSections :: SectionParam -> Trace [Section] Source # getSection :: SectionId -> Trace Section Source # addSection :: SectionCreate -> Trace SectionId Source # updateSection :: SectionUpdate -> SectionId -> Trace Section Source # deleteSection :: SectionId -> Trace () Source # getSectionsPaginated :: SectionParam -> Trace ([Section], Maybe Text) Source # | |
Constructors
newSectionBuilder :: Text -> Text -> Initial SectionCreate Source #
Smart constructor for creating a new section
updateSectionBuilder :: Initial SectionUpdate Source #
Empty section update for builder pattern
sectionParamBuilder :: Initial SectionParam Source #
Create new SectionParam for use with builder pattern