yu-core-0.1.1.2: The core of Yu.

Safe HaskellNone
LanguageHaskell2010

Yu.Core.Model.Internal

Contents

Description

Model : Yu.Core.Model.Internal Description : The basic methods for model and types Copyright : (C) 2017-2018 Johann Lee me@qinka.pro License : GPL3 Maintainer : me@qinka.pro Stability : experimental Portability : unknown

The basic method and type for model in MVC

Synopsis

navigation bar

data Nav Source #

model for navigation bar

Constructors

Nav 

Fields

Instances

Eq Nav Source #

instance eq, order for nav

Methods

(==) :: Nav -> Nav -> Bool #

(/=) :: Nav -> Nav -> Bool #

Ord Nav Source # 

Methods

compare :: Nav -> Nav -> Ordering #

(<) :: Nav -> Nav -> Bool #

(<=) :: Nav -> Nav -> Bool #

(>) :: Nav -> Nav -> Bool #

(>=) :: Nav -> Nav -> Bool #

max :: Nav -> Nav -> Nav #

min :: Nav -> Nav -> Nav #

Show Nav Source # 

Methods

showsPrec :: Int -> Nav -> ShowS #

show :: Nav -> String #

showList :: [Nav] -> ShowS #

ToJSON Nav Source #

instance Json(to)

navToDoc :: Nav -> Document Source #

transform between nav and document

docToNav :: Document -> Maybe Nav Source #

transform Document to nav

the resource

data ResT Source #

the resource type for item

Constructors

ResT 

Fields

Instances

resToDoc :: ResT -> Document Source #

transform between res document

docToRes :: Document -> Maybe ResT Source #

transform between res document

transform

fromBinary :: Binary -> ByteString Source #

Binary to ByteString

about mongoDB

class (MonadIO m, MonadBaseControl IO m) => Mongodic a m | m -> a where Source #

the type-class which means mongoDB available.

Minimal complete definition

getDefaultAccessMode, getDefaultDb, getDbUP, getPool

Methods

getDefaultAccessMode Source #

Arguments

:: m AccessMode

get the accedd mode

getDefaultDb Source #

Arguments

:: m Database

get the default database

getDbUP Source #

Arguments

:: m (Text, Text)

get the user and pass

getPool Source #

Arguments

:: m ConnectionPool

get the connection pool

type ConnectionPool = Pool Pipe Source #

ConnectionPool

fetchContext Source #

Arguments

:: (MonadIO m, Val a) 
=> Text

field name

-> ResT

resource index

-> Text

collection

-> Action m (Maybe a)

result

fetch context

fetchRes :: MonadIO m => [Text] -> Action m (Maybe ResT) Source #

fetch resource index

fetchResAll :: (MonadIO m, MonadBaseControl IO m) => Action m [ResT] Source #

fetch all resource index

updateContext Source #

Arguments

:: (MonadIO m, Val a) 
=> Text

collection

-> Maybe ObjectId

obj id of item

-> Text

field name

-> a 
-> Action m ObjectId

return id

update context

updateItem Source #

Arguments

:: (MonadIO m, Val a) 
=> Text

type, or say collection

-> Text

field name

-> a

item

-> ResT

`undefined' ResT

-> Action m () 

the update for item

updateRes Source #

Arguments

:: MonadIO m 
=> ResT

the index

-> Action m () 

the update for resource

deleteContext Source #

Arguments

:: MonadIO m 
=> ResT

index

-> Text

collection

-> Action m () 

delete the context

deleteItem Source #

Arguments

:: MonadIO m 
=> [Text]

url

-> Text

collection

-> Action m () 

delete item

deleteRes Source #

Arguments

:: MonadIO m 
=> ResT

index

-> Action m () 

delete resource

deleteContextMaybe Source #

Arguments

:: MonadIO m 
=> Maybe ResT

index

-> Action m () 

delete the resouce in maybe

(=@) infix 0 Source #

Arguments

:: Val v 
=> Label

label

-> Maybe v

value

-> Maybe Field

maybe field

update nothing

module Data.Pool