todoist-sdk-0.1.2.1: Unofficial Haskell SDK for the Todoist REST API
Copyright(c) 2025 Sam S. Almahri
LicenseMIT
Maintainer[email protected]
Safe HaskellNone
LanguageHaskell2010

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

Types

data Section Source #

Simplified domain representation of a Section (5 essential fields) Note: API returns 11 fields, but we only expose the essential ones

Instances

Instances details
Generic Section Source # 
Instance details

Defined in Web.Todoist.Domain.Section

Associated Types

type Rep Section 
Instance details

Defined in Web.Todoist.Domain.Section

Methods

from :: Section -> Rep Section x #

to :: Rep Section x -> Section #

Show Section Source # 
Instance details

Defined in Web.Todoist.Domain.Section

type Rep Section Source # 
Instance details

Defined in Web.Todoist.Domain.Section

newtype SectionId Source #

Unique identifier for a Section

Constructors

SectionId 

Fields

Instances

Instances details
FromJSON SectionId Source # 
Instance details

Defined in Web.Todoist.Domain.Section

ToJSON SectionId Source # 
Instance details

Defined in Web.Todoist.Domain.Section

Generic SectionId Source # 
Instance details

Defined in Web.Todoist.Domain.Section

Associated Types

type Rep SectionId 
Instance details

Defined in Web.Todoist.Domain.Section

type Rep SectionId = D1 ('MetaData "SectionId" "Web.Todoist.Domain.Section" "todoist-sdk-0.1.2.1-DGBtxdXKO1e8ZQYcxjFTC8" 'True) (C1 ('MetaCons "SectionId" 'PrefixI 'True) (S1 ('MetaSel ('Just "_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))
Show SectionId Source # 
Instance details

Defined in Web.Todoist.Domain.Section

Eq SectionId Source # 
Instance details

Defined in Web.Todoist.Domain.Section

type Rep SectionId Source # 
Instance details

Defined in Web.Todoist.Domain.Section

type Rep SectionId = D1 ('MetaData "SectionId" "Web.Todoist.Domain.Section" "todoist-sdk-0.1.2.1-DGBtxdXKO1e8ZQYcxjFTC8" 'True) (C1 ('MetaCons "SectionId" 'PrefixI 'True) (S1 ('MetaSel ('Just "_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data SectionCreate Source #

Request body for creating a new Section

Instances

Instances details
ToJSON SectionCreate Source # 
Instance details

Defined in Web.Todoist.Domain.Section

Generic SectionCreate Source # 
Instance details

Defined in Web.Todoist.Domain.Section

Associated Types

type Rep SectionCreate 
Instance details

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)))))
Show SectionCreate Source # 
Instance details

Defined in Web.Todoist.Domain.Section

HasName SectionCreate Source # 
Instance details

Defined in Web.Todoist.Domain.Section

HasOrder SectionCreate Source # 
Instance details

Defined in Web.Todoist.Domain.Section

type Rep SectionCreate Source # 
Instance details

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

Instances details
ToJSON SectionUpdate Source # 
Instance details

Defined in Web.Todoist.Domain.Section

Generic SectionUpdate Source # 
Instance details

Defined in Web.Todoist.Domain.Section

Associated Types

type Rep SectionUpdate 
Instance details

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))))
Show SectionUpdate Source # 
Instance details

Defined in Web.Todoist.Domain.Section

HasName SectionUpdate Source # 
Instance details

Defined in Web.Todoist.Domain.Section

type Rep SectionUpdate Source # 
Instance details

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

Instances

Instances details
Generic SectionParam Source # 
Instance details

Defined in Web.Todoist.Domain.Section

Associated Types

type Rep SectionParam 
Instance details

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)))))
Show SectionParam Source # 
Instance details

Defined in Web.Todoist.Domain.Section

HasCursor SectionParam Source # 
Instance details

Defined in Web.Todoist.Domain.Section

HasLimit SectionParam Source # 
Instance details

Defined in Web.Todoist.Domain.Section

HasProjectId SectionParam Source # 
Instance details

Defined in Web.Todoist.Domain.Section

QueryParam SectionParam Source # 
Instance details

Defined in Web.Todoist.Domain.Section

type Rep SectionParam Source # 
Instance details

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

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

Lenses

sectionId :: Getter Section SectionId Source #

Lenses for Section