clckwrks-0.26.3: A secure, reliable content management system (CMS) and blogging platform
Safe HaskellNone
LanguageHaskell2010

Clckwrks

Synopsis

Documentation

newtype UserId #

a UserId uniquely identifies a user.

Constructors

UserId 

Fields

Instances

Instances details
Enum UserId 
Instance details

Defined in Data.UserId

Eq UserId 
Instance details

Defined in Data.UserId

Methods

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

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

Data UserId 
Instance details

Defined in Data.UserId

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UserId -> c UserId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UserId #

toConstr :: UserId -> Constr #

dataTypeOf :: UserId -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UserId) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserId) #

gmapT :: (forall b. Data b => b -> b) -> UserId -> UserId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserId -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserId -> r #

gmapQ :: (forall d. Data d => d -> u) -> UserId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UserId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UserId -> m UserId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UserId -> m UserId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UserId -> m UserId #

Ord UserId 
Instance details

Defined in Data.UserId

Read UserId 
Instance details

Defined in Data.UserId

Show UserId 
Instance details

Defined in Data.UserId

Generic UserId 
Instance details

Defined in Data.UserId

Associated Types

type Rep UserId :: Type -> Type #

Methods

from :: UserId -> Rep UserId x #

to :: Rep UserId x -> UserId #

SafeCopy UserId 
Instance details

Defined in Data.UserId

ToJSON UserId 
Instance details

Defined in Data.UserId

FromJSON UserId 
Instance details

Defined in Data.UserId

Serialize UserId 
Instance details

Defined in Data.UserId

PathInfo UserId 
Instance details

Defined in Data.UserId

Indexable UserIxs User 
Instance details

Defined in Happstack.Authenticate.Core

type Rep UserId 
Instance details

Defined in Data.UserId

type Rep UserId = D1 ('MetaData "UserId" "Data.UserId" "userid-0.1.3.5-43lF2UnxQu99ZsiN9RInqY" 'True) (C1 ('MetaCons "UserId" 'PrefixI 'True) (S1 ('MetaSel ('Just "_unUserId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))

data JStat #

Statements

Instances

Instances details
Eq JStat 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

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

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

Data JStat 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JStat -> c JStat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JStat #

toConstr :: JStat -> Constr #

dataTypeOf :: JStat -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JStat) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JStat) #

gmapT :: (forall b. Data b => b -> b) -> JStat -> JStat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JStat -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JStat -> r #

gmapQ :: (forall d. Data d => d -> u) -> JStat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JStat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JStat -> m JStat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JStat -> m JStat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JStat -> m JStat #

Ord JStat 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

compare :: JStat -> JStat -> Ordering #

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

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

(>) :: JStat -> JStat -> Bool #

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

max :: JStat -> JStat -> JStat #

min :: JStat -> JStat -> JStat #

Show JStat 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

showsPrec :: Int -> JStat -> ShowS #

show :: JStat -> String #

showList :: [JStat] -> ShowS #

Semigroup JStat 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

(<>) :: JStat -> JStat -> JStat #

sconcat :: NonEmpty JStat -> JStat #

stimes :: Integral b => b -> JStat -> JStat #

Monoid JStat 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

mempty :: JStat #

mappend :: JStat -> JStat -> JStat #

mconcat :: [JStat] -> JStat #

JMacro JStat 
Instance details

Defined in Language.Javascript.JMacro.Base

JsToDoc JStat 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

jsToDoc :: JStat -> Doc #

ToStat JStat 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

toStat :: JStat -> JStat #

ToSat JStat 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

toSat_ :: JStat -> [Ident] -> IdentSupply (JStat, [Ident])

JsToDoc [JStat] 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

jsToDoc :: [JStat] -> Doc #

ToStat [JStat] 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

toStat :: [JStat] -> JStat #

ToSat [JStat] 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

toSat_ :: [JStat] -> [Ident] -> IdentSupply (JStat, [Ident])

jmacroE :: QuasiQuoter #

QuasiQuoter for a JMacro expression.

jmacro :: QuasiQuoter #

QuasiQuoter for a block of JMacro statements.

data JExpr #

Expressions

Instances

Instances details
Eq JExpr 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

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

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

Data JExpr 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JExpr -> c JExpr #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JExpr #

toConstr :: JExpr -> Constr #

dataTypeOf :: JExpr -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JExpr) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JExpr) #

gmapT :: (forall b. Data b => b -> b) -> JExpr -> JExpr #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JExpr -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JExpr -> r #

gmapQ :: (forall d. Data d => d -> u) -> JExpr -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JExpr -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JExpr -> m JExpr #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JExpr -> m JExpr #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JExpr -> m JExpr #

Num JExpr 
Instance details

Defined in Language.Javascript.JMacro.Base

Ord JExpr 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

compare :: JExpr -> JExpr -> Ordering #

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

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

(>) :: JExpr -> JExpr -> Bool #

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

max :: JExpr -> JExpr -> JExpr #

min :: JExpr -> JExpr -> JExpr #

Show JExpr 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

showsPrec :: Int -> JExpr -> ShowS #

show :: JExpr -> String #

showList :: [JExpr] -> ShowS #

JMacro JExpr 
Instance details

Defined in Language.Javascript.JMacro.Base

JsToDoc JExpr 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

jsToDoc :: JExpr -> Doc #

ToJExpr JExpr 
Instance details

Defined in Language.Javascript.JMacro.Base

ToStat JExpr 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

toStat :: JExpr -> JStat #

ToSat JExpr 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

toSat_ :: JExpr -> [Ident] -> IdentSupply (JStat, [Ident])

JsToDoc [JExpr] 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

jsToDoc :: [JExpr] -> Doc #

ToStat [JExpr] 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

toStat :: [JExpr] -> JStat #

ToSat [JExpr] 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

toSat_ :: [JExpr] -> [Ident] -> IdentSupply (JStat, [Ident])

data JVal #

Values

Instances

Instances details
Eq JVal 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

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

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

Data JVal 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JVal -> c JVal #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JVal #

toConstr :: JVal -> Constr #

dataTypeOf :: JVal -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JVal) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JVal) #

gmapT :: (forall b. Data b => b -> b) -> JVal -> JVal #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JVal -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JVal -> r #

gmapQ :: (forall d. Data d => d -> u) -> JVal -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JVal -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JVal -> m JVal #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JVal -> m JVal #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JVal -> m JVal #

Ord JVal 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

compare :: JVal -> JVal -> Ordering #

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

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

(>) :: JVal -> JVal -> Bool #

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

max :: JVal -> JVal -> JVal #

min :: JVal -> JVal -> JVal #

Show JVal 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

showsPrec :: Int -> JVal -> ShowS #

show :: JVal -> String #

showList :: [JVal] -> ShowS #

JMacro JVal 
Instance details

Defined in Language.Javascript.JMacro.Base

JsToDoc JVal 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

jsToDoc :: JVal -> Doc #

ToJExpr JVal 
Instance details

Defined in Language.Javascript.JMacro.Base

newtype Ident #

Identifiers

Constructors

StrI String 

Instances

Instances details
Eq Ident 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

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

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

Data Ident 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ident -> c Ident #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ident #

toConstr :: Ident -> Constr #

dataTypeOf :: Ident -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Ident) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ident) #

gmapT :: (forall b. Data b => b -> b) -> Ident -> Ident #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r #

gmapQ :: (forall d. Data d => d -> u) -> Ident -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ident -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ident -> m Ident #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ident -> m Ident #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ident -> m Ident #

Ord Ident 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

compare :: Ident -> Ident -> Ordering #

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

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

(>) :: Ident -> Ident -> Bool #

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

max :: Ident -> Ident -> Ident #

min :: Ident -> Ident -> Ident #

Show Ident 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

JMacro Ident 
Instance details

Defined in Language.Javascript.JMacro.Base

JsToDoc Ident 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

jsToDoc :: Ident -> Doc #

class JMacro a where #

Compos and ops for generic traversal as defined over the JMacro ADT.

Utility class to coerce the ADT into a regular structure.

Methods

jtoGADT :: a -> JMGadt a #

jfromGADT :: JMGadt a -> a #

Instances

Instances details
JMacro JStat 
Instance details

Defined in Language.Javascript.JMacro.Base

JMacro JExpr 
Instance details

Defined in Language.Javascript.JMacro.Base

JMacro JVal 
Instance details

Defined in Language.Javascript.JMacro.Base

JMacro Ident 
Instance details

Defined in Language.Javascript.JMacro.Base

toJExpr :: ToJExpr a => a -> JExpr #

data JType #

Instances

Instances details
Eq JType 
Instance details

Defined in Language.Javascript.JMacro.Types

Methods

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

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

Data JType 
Instance details

Defined in Language.Javascript.JMacro.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JType -> c JType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JType #

toConstr :: JType -> Constr #

dataTypeOf :: JType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JType) #

gmapT :: (forall b. Data b => b -> b) -> JType -> JType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JType -> r #

gmapQ :: (forall d. Data d => d -> u) -> JType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JType -> m JType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JType -> m JType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JType -> m JType #

Ord JType 
Instance details

Defined in Language.Javascript.JMacro.Types

Methods

compare :: JType -> JType -> Ordering #

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

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

(>) :: JType -> JType -> Bool #

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

max :: JType -> JType -> JType #

min :: JType -> JType -> JType #

Read JType 
Instance details

Defined in Language.Javascript.JMacro.Types

Show JType 
Instance details

Defined in Language.Javascript.JMacro.Types

Methods

showsPrec :: Int -> JType -> ShowS #

show :: JType -> String #

showList :: [JType] -> ShowS #

JsToDoc JType 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

jsToDoc :: JType -> Doc #

JsToDoc JLocalType 
Instance details

Defined in Language.Javascript.JMacro.Base

Methods

jsToDoc :: JLocalType -> Doc #

class Generic a #

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

A Generic instance must satisfy the following laws:

from . toid
to . fromid

Minimal complete definition

from, to

Instances

Instances details
Generic Bool

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Bool :: Type -> Type #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Generic Ordering

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Ordering :: Type -> Type #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Generic Exp 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Exp :: Type -> Type #

Methods

from :: Exp -> Rep Exp x #

to :: Rep Exp x -> Exp #

Generic Match 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Match :: Type -> Type #

Methods

from :: Match -> Rep Match x #

to :: Rep Match x -> Match #

Generic Clause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Clause :: Type -> Type #

Methods

from :: Clause -> Rep Clause x #

to :: Rep Clause x -> Clause #

Generic Pat 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Pat :: Type -> Type #

Methods

from :: Pat -> Rep Pat x #

to :: Rep Pat x -> Pat #

Generic Type 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Type :: Type -> Type #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

Generic Dec 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Dec :: Type -> Type #

Methods

from :: Dec -> Rep Dec x #

to :: Rep Dec x -> Dec #

Generic Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Name :: Type -> Type #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

Generic FunDep 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FunDep :: Type -> Type #

Methods

from :: FunDep -> Rep FunDep x #

to :: Rep FunDep x -> FunDep #

Generic InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep InjectivityAnn :: Type -> Type #

Generic Overlap 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Overlap :: Type -> Type #

Methods

from :: Overlap -> Rep Overlap x #

to :: Rep Overlap x -> Overlap #

Generic ()

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep () :: Type -> Type #

Methods

from :: () -> Rep () x #

to :: Rep () x -> () #

Generic TyVarBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TyVarBndr :: Type -> Type #

Generic Value 
Instance details

Defined in Data.Aeson.Types.Internal

Associated Types

type Rep Value :: Type -> Type #

Methods

from :: Value -> Rep Value x #

to :: Rep Value x -> Value #

Generic Void

Since: base-4.8.0.0

Instance details

Defined in Data.Void

Associated Types

type Rep Void :: Type -> Type #

Methods

from :: Void -> Rep Void x #

to :: Rep Void x -> Void #

Generic Version

Since: base-4.9.0.0

Instance details

Defined in Data.Version

Associated Types

type Rep Version :: Type -> Type #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Generic ExitCode 
Instance details

Defined in GHC.IO.Exception

Associated Types

type Rep ExitCode :: Type -> Type #

Methods

from :: ExitCode -> Rep ExitCode x #

to :: Rep ExitCode x -> ExitCode #

Generic All

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep All :: Type -> Type #

Methods

from :: All -> Rep All x #

to :: Rep All x -> All #

Generic Any

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep Any :: Type -> Type #

Methods

from :: Any -> Rep Any x #

to :: Rep Any x -> Any #

Generic Fixity

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Fixity :: Type -> Type #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic Associativity

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Associativity :: Type -> Type #

Generic SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceUnpackedness :: Type -> Type #

Generic SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceStrictness :: Type -> Type #

Generic DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep DecidedStrictness :: Type -> Type #

Generic WindowBits 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep WindowBits :: Type -> Type #

Generic EmailAddress 
Instance details

Defined in Text.Email.Parser

Associated Types

type Rep EmailAddress :: Type -> Type #

Generic Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

Associated Types

type Rep Extension :: Type -> Type #

Generic ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Associated Types

type Rep ForeignSrcLang :: Type -> Type #

Generic ResetPasswordData 
Instance details

Defined in Happstack.Authenticate.Password.Core

Associated Types

type Rep ResetPasswordData :: Type -> Type #

Generic RequestResetPasswordData 
Instance details

Defined in Happstack.Authenticate.Password.Core

Associated Types

type Rep RequestResetPasswordData :: Type -> Type #

Generic ChangePasswordData 
Instance details

Defined in Happstack.Authenticate.Password.Core

Associated Types

type Rep ChangePasswordData :: Type -> Type #

Generic NewAccountData 
Instance details

Defined in Happstack.Authenticate.Password.Core

Associated Types

type Rep NewAccountData :: Type -> Type #

Generic UserPass 
Instance details

Defined in Happstack.Authenticate.Password.Core

Associated Types

type Rep UserPass :: Type -> Type #

Methods

from :: UserPass -> Rep UserPass x #

to :: Rep UserPass x -> UserPass #

Generic PasswordState 
Instance details

Defined in Happstack.Authenticate.Password.Core

Associated Types

type Rep PasswordState :: Type -> Type #

Generic HashedPass 
Instance details

Defined in Happstack.Authenticate.Password.Core

Associated Types

type Rep HashedPass :: Type -> Type #

Generic PasswordError 
Instance details

Defined in Happstack.Authenticate.Password.Core

Associated Types

type Rep PasswordError :: Type -> Type #

Generic PasswordConfig 
Instance details

Defined in Happstack.Authenticate.Password.Core

Associated Types

type Rep PasswordConfig :: Type -> Type #

Generic PasswordURL 
Instance details

Defined in Happstack.Authenticate.Password.URL

Associated Types

type Rep PasswordURL :: Type -> Type #

Generic AccountURL 
Instance details

Defined in Happstack.Authenticate.Password.URL

Associated Types

type Rep AccountURL :: Type -> Type #

Generic PartialURL 
Instance details

Defined in Happstack.Authenticate.Password.PartialsURL

Associated Types

type Rep PartialURL :: Type -> Type #

Generic SetRealmData 
Instance details

Defined in Happstack.Authenticate.OpenId.Core

Associated Types

type Rep SetRealmData :: Type -> Type #

Generic OpenIdState 
Instance details

Defined in Happstack.Authenticate.OpenId.Core

Associated Types

type Rep OpenIdState :: Type -> Type #

Generic OpenIdState_1 
Instance details

Defined in Happstack.Authenticate.OpenId.Core

Associated Types

type Rep OpenIdState_1 :: Type -> Type #

Generic OpenIdError 
Instance details

Defined in Happstack.Authenticate.OpenId.Core

Associated Types

type Rep OpenIdError :: Type -> Type #

Generic OpenIdURL 
Instance details

Defined in Happstack.Authenticate.OpenId.URL

Associated Types

type Rep OpenIdURL :: Type -> Type #

Generic PartialURL 
Instance details

Defined in Happstack.Authenticate.OpenId.PartialsURL

Associated Types

type Rep PartialURL :: Type -> Type #

Generic AuthenticateURL 
Instance details

Defined in Happstack.Authenticate.Core

Associated Types

type Rep AuthenticateURL :: Type -> Type #

Generic AuthenticationMethod 
Instance details

Defined in Happstack.Authenticate.Core

Associated Types

type Rep AuthenticationMethod :: Type -> Type #

Generic Token 
Instance details

Defined in Happstack.Authenticate.Core

Associated Types

type Rep Token :: Type -> Type #

Methods

from :: Token -> Rep Token x #

to :: Rep Token x -> Token #

Generic AuthenticateState 
Instance details

Defined in Happstack.Authenticate.Core

Associated Types

type Rep AuthenticateState :: Type -> Type #

Generic NewAccountMode 
Instance details

Defined in Happstack.Authenticate.Core

Associated Types

type Rep NewAccountMode :: Type -> Type #

Generic SharedSecret 
Instance details

Defined in Happstack.Authenticate.Core

Associated Types

type Rep SharedSecret :: Type -> Type #

Generic AuthenticateConfig 
Instance details

Defined in Happstack.Authenticate.Core

Associated Types

type Rep AuthenticateConfig :: Type -> Type #

Generic SimpleAddress 
Instance details

Defined in Happstack.Authenticate.Core

Associated Types

type Rep SimpleAddress :: Type -> Type #

Generic User 
Instance details

Defined in Happstack.Authenticate.Core

Associated Types

type Rep User :: Type -> Type #

Methods

from :: User -> Rep User x #

to :: Rep User x -> User #

Generic Email 
Instance details

Defined in Happstack.Authenticate.Core

Associated Types

type Rep Email :: Type -> Type #

Methods

from :: Email -> Rep Email x #

to :: Rep Email x -> Email #

Generic Username 
Instance details

Defined in Happstack.Authenticate.Core

Associated Types

type Rep Username :: Type -> Type #

Methods

from :: Username -> Rep Username x #

to :: Rep Username x -> Username #

Generic CoreError 
Instance details

Defined in Happstack.Authenticate.Core

Associated Types

type Rep CoreError :: Type -> Type #

Generic UserId 
Instance details

Defined in Data.UserId

Associated Types

type Rep UserId :: Type -> Type #

Methods

from :: UserId -> Rep UserId x #

to :: Rep UserId x -> UserId #

Generic Boxed 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep Boxed :: Type -> Type #

Methods

from :: Boxed -> Rep Boxed x #

to :: Rep Boxed x -> Boxed #

Generic Tool 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep Tool :: Type -> Type #

Methods

from :: Tool -> Rep Tool x #

to :: Rep Tool x -> Tool #

Generic SrcLoc 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Associated Types

type Rep SrcLoc :: Type -> Type #

Methods

from :: SrcLoc -> Rep SrcLoc x #

to :: Rep SrcLoc x -> SrcLoc #

Generic SrcSpan 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Associated Types

type Rep SrcSpan :: Type -> Type #

Methods

from :: SrcSpan -> Rep SrcSpan x #

to :: Rep SrcSpan x -> SrcSpan #

Generic SrcSpanInfo 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Associated Types

type Rep SrcSpanInfo :: Type -> Type #

Generic Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Mode :: Type -> Type #

Methods

from :: Mode -> Rep Mode x #

to :: Rep Mode x -> Mode #

Generic Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Style :: Type -> Type #

Methods

from :: Style -> Rep Style x #

to :: Rep Style x -> Style #

Generic Priority 
Instance details

Defined in System.Log

Associated Types

type Rep Priority :: Type -> Type #

Methods

from :: Priority -> Rep Priority x #

to :: Rep Priority x -> Priority #

Generic URI 
Instance details

Defined in Network.URI

Associated Types

type Rep URI :: Type -> Type #

Methods

from :: URI -> Rep URI x #

to :: Rep URI x -> URI #

Generic RuleBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleBndr :: Type -> Type #

Methods

from :: RuleBndr -> Rep RuleBndr x #

to :: Rep RuleBndr x -> RuleBndr #

Generic Phases 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Phases :: Type -> Type #

Methods

from :: Phases -> Rep Phases x #

to :: Rep Phases x -> Phases #

Generic RuleMatch 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleMatch :: Type -> Type #

Generic Inline 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Inline :: Type -> Type #

Methods

from :: Inline -> Rep Inline x #

to :: Rep Inline x -> Inline #

Generic Pragma 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Pragma :: Type -> Type #

Methods

from :: Pragma -> Rep Pragma x #

to :: Rep Pragma x -> Pragma #

Generic DerivClause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivClause :: Type -> Type #

Generic DerivStrategy 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivStrategy :: Type -> Type #

Generic TySynEqn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TySynEqn :: Type -> Type #

Methods

from :: TySynEqn -> Rep TySynEqn x #

to :: Rep TySynEqn x -> TySynEqn #

Generic Fixity 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Fixity :: Type -> Type #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic Info 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Info :: Type -> Type #

Methods

from :: Info -> Rep Info x #

to :: Rep Info x -> Info #

Generic Con 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Con :: Type -> Type #

Methods

from :: Con -> Rep Con x #

to :: Rep Con x -> Con #

Generic URIAuth 
Instance details

Defined in Network.URI

Associated Types

type Rep URIAuth :: Type -> Type #

Methods

from :: URIAuth -> Rep URIAuth x #

to :: Rep URIAuth x -> URIAuth #

Generic Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Associated Types

type Rep Doc :: Type -> Type #

Methods

from :: Doc -> Rep Doc x #

to :: Rep Doc x -> Doc #

Generic TextDetails 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep TextDetails :: Type -> Type #

Generic ModName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModName :: Type -> Type #

Methods

from :: ModName -> Rep ModName x #

to :: Rep ModName x -> ModName #

Generic PkgName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PkgName :: Type -> Type #

Methods

from :: PkgName -> Rep PkgName x #

to :: Rep PkgName x -> PkgName #

Generic Module 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Module :: Type -> Type #

Methods

from :: Module -> Rep Module x #

to :: Rep Module x -> Module #

Generic OccName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep OccName :: Type -> Type #

Methods

from :: OccName -> Rep OccName x #

to :: Rep OccName x -> OccName #

Generic NameFlavour 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameFlavour :: Type -> Type #

Generic NameSpace 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameSpace :: Type -> Type #

Generic Loc 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Loc :: Type -> Type #

Methods

from :: Loc -> Rep Loc x #

to :: Rep Loc x -> Loc #

Generic ModuleInfo 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModuleInfo :: Type -> Type #

Generic FixityDirection 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FixityDirection :: Type -> Type #

Generic Lit 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Lit :: Type -> Type #

Methods

from :: Lit -> Rep Lit x #

to :: Rep Lit x -> Lit #

Generic Bytes 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Bytes :: Type -> Type #

Methods

from :: Bytes -> Rep Bytes x #

to :: Rep Bytes x -> Bytes #

Generic Body 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Body :: Type -> Type #

Methods

from :: Body -> Rep Body x #

to :: Rep Body x -> Body #

Generic Guard 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Guard :: Type -> Type #

Methods

from :: Guard -> Rep Guard x #

to :: Rep Guard x -> Guard #

Generic Stmt 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Stmt :: Type -> Type #

Methods

from :: Stmt -> Rep Stmt x #

to :: Rep Stmt x -> Stmt #

Generic Range 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Range :: Type -> Type #

Methods

from :: Range -> Rep Range x #

to :: Rep Range x -> Range #

Generic TypeFamilyHead 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TypeFamilyHead :: Type -> Type #

Generic Foreign 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Foreign :: Type -> Type #

Methods

from :: Foreign -> Rep Foreign x #

to :: Rep Foreign x -> Foreign #

Generic Callconv 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Callconv :: Type -> Type #

Methods

from :: Callconv -> Rep Callconv x #

to :: Rep Callconv x -> Callconv #

Generic Safety 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Safety :: Type -> Type #

Methods

from :: Safety -> Rep Safety x #

to :: Rep Safety x -> Safety #

Generic AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnTarget :: Type -> Type #

Generic SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceUnpackedness :: Type -> Type #

Generic SourceStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceStrictness :: Type -> Type #

Generic DecidedStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DecidedStrictness :: Type -> Type #

Generic Bang 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Bang :: Type -> Type #

Methods

from :: Bang -> Rep Bang x #

to :: Rep Bang x -> Bang #

Generic PatSynDir 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynDir :: Type -> Type #

Generic PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynArgs :: Type -> Type #

Generic FamilyResultSig 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FamilyResultSig :: Type -> Type #

Generic TyLit 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TyLit :: Type -> Type #

Methods

from :: TyLit -> Rep TyLit x #

to :: Rep TyLit x -> TyLit #

Generic Role 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Role :: Type -> Type #

Methods

from :: Role -> Rep Role x #

to :: Rep Role x -> Role #

Generic AnnLookup 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnLookup :: Type -> Type #

Generic DatatypeInfo 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep DatatypeInfo :: Type -> Type #

Generic DatatypeVariant 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep DatatypeVariant :: Type -> Type #

Generic ConstructorInfo 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep ConstructorInfo :: Type -> Type #

Generic ConstructorVariant 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep ConstructorVariant :: Type -> Type #

Generic FieldStrictness 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep FieldStrictness :: Type -> Type #

Generic Unpackedness 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep Unpackedness :: Type -> Type #

Generic Strictness 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep Strictness :: Type -> Type #

Generic Event 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Event :: Type -> Type #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

Generic ExternalID 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep ExternalID :: Type -> Type #

Generic Doctype 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Doctype :: Type -> Type #

Methods

from :: Doctype -> Rep Doctype x #

to :: Rep Doctype x -> Doctype #

Generic Name 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Name :: Type -> Type #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

Generic Miscellaneous 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Miscellaneous :: Type -> Type #

Generic Instruction 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Instruction :: Type -> Type #

Generic Prologue 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Prologue :: Type -> Type #

Methods

from :: Prologue -> Rep Prologue x #

to :: Rep Prologue x -> Prologue #

Generic Document 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Document :: Type -> Type #

Methods

from :: Document -> Rep Document x #

to :: Rep Document x -> Document #

Generic Node 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Node :: Type -> Type #

Methods

from :: Node -> Rep Node x #

to :: Rep Node x -> Node #

Generic Element 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Element :: Type -> Type #

Methods

from :: Element -> Rep Element x #

to :: Rep Element x -> Element #

Generic Content 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Content :: Type -> Type #

Methods

from :: Content -> Rep Content x #

to :: Rep Content x -> Content #

Generic Format 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep Format :: Type -> Type #

Methods

from :: Format -> Rep Format x #

to :: Rep Format x -> Format #

Generic Method 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep Method :: Type -> Type #

Methods

from :: Method -> Rep Method x #

to :: Rep Method x -> Method #

Generic CompressionLevel 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep CompressionLevel :: Type -> Type #

Generic MemoryLevel 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep MemoryLevel :: Type -> Type #

Generic CompressionStrategy 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep CompressionStrategy :: Type -> Type #

Generic JSONResponse 
Instance details

Defined in Happstack.Authenticate.Core

Associated Types

type Rep JSONResponse :: Type -> Type #

Methods

from :: JSONResponse -> Rep JSONResponse x #

to :: Rep JSONResponse x -> JSONResponse #

Generic Status 
Instance details

Defined in Happstack.Authenticate.Core

Associated Types

type Rep Status :: Type -> Type #

Methods

from :: Status -> Rep Status x #

to :: Rep Status x -> Status #

Generic AuthURL Source # 
Instance details

Defined in Clckwrks.Authenticate.URL

Associated Types

type Rep AuthURL :: Type -> Type #

Methods

from :: AuthURL -> Rep AuthURL x #

to :: Rep AuthURL x -> AuthURL #

Generic JSURL Source # 
Instance details

Defined in Clckwrks.JS.URL

Associated Types

type Rep JSURL :: Type -> Type #

Methods

from :: JSURL -> Rep JSURL x #

to :: Rep JSURL x -> JSURL #

Generic Role Source # 
Instance details

Defined in Clckwrks.ProfileData.Types

Associated Types

type Rep Role :: Type -> Type #

Methods

from :: Role -> Rep Role x #

to :: Rep Role x -> Role #

Generic DisplayName Source # 
Instance details

Defined in Clckwrks.ProfileData.Types

Associated Types

type Rep DisplayName :: Type -> Type #

Generic Username Source # 
Instance details

Defined in Clckwrks.ProfileData.Types

Associated Types

type Rep Username :: Type -> Type #

Methods

from :: Username -> Rep Username x #

to :: Rep Username x -> Username #

Generic ProfileData Source # 
Instance details

Defined in Clckwrks.ProfileData.Types

Associated Types

type Rep ProfileData :: Type -> Type #

Generic [a]

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep [a] :: Type -> Type #

Methods

from :: [a] -> Rep [a] x #

to :: Rep [a] x -> [a] #

Generic (Maybe a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Maybe a) :: Type -> Type #

Methods

from :: Maybe a -> Rep (Maybe a) x #

to :: Rep (Maybe a) x -> Maybe a #

Generic (Par1 p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Par1 p) :: Type -> Type #

Methods

from :: Par1 p -> Rep (Par1 p) x #

to :: Rep (Par1 p) x -> Par1 p #

Generic (Complex a)

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

Associated Types

type Rep (Complex a) :: Type -> Type #

Methods

from :: Complex a -> Rep (Complex a) x #

to :: Rep (Complex a) x -> Complex a #

Generic (Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Min a) :: Type -> Type #

Methods

from :: Min a -> Rep (Min a) x #

to :: Rep (Min a) x -> Min a #

Generic (Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Max a) :: Type -> Type #

Methods

from :: Max a -> Rep (Max a) x #

to :: Rep (Max a) x -> Max a #

Generic (First a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (First a) :: Type -> Type #

Methods

from :: First a -> Rep (First a) x #

to :: Rep (First a) x -> First a #

Generic (Last a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Last a) :: Type -> Type #

Methods

from :: Last a -> Rep (Last a) x #

to :: Rep (Last a) x -> Last a #

Generic (WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (WrappedMonoid m) :: Type -> Type #

Generic (Option a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Option a) :: Type -> Type #

Methods

from :: Option a -> Rep (Option a) x #

to :: Rep (Option a) x -> Option a #

Generic (ZipList a)

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

Associated Types

type Rep (ZipList a) :: Type -> Type #

Methods

from :: ZipList a -> Rep (ZipList a) x #

to :: Rep (ZipList a) x -> ZipList a #

Generic (Identity a)

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Associated Types

type Rep (Identity a) :: Type -> Type #

Methods

from :: Identity a -> Rep (Identity a) x #

to :: Rep (Identity a) x -> Identity a #

Generic (First a)

Since: base-4.7.0.0

Instance details

Defined in Data.Monoid

Associated Types

type Rep (First a) :: Type -> Type #

Methods

from :: First a -> Rep (First a) x #

to :: Rep (First a) x -> First a #

Generic (Last a)

Since: base-4.7.0.0

Instance details

Defined in Data.Monoid

Associated Types

type Rep (Last a) :: Type -> Type #

Methods

from :: Last a -> Rep (Last a) x #

to :: Rep (Last a) x -> Last a #

Generic (Dual a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Dual a) :: Type -> Type #

Methods

from :: Dual a -> Rep (Dual a) x #

to :: Rep (Dual a) x -> Dual a #

Generic (Endo a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Endo a) :: Type -> Type #

Methods

from :: Endo a -> Rep (Endo a) x #

to :: Rep (Endo a) x -> Endo a #

Generic (Sum a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Sum a) :: Type -> Type #

Methods

from :: Sum a -> Rep (Sum a) x #

to :: Rep (Sum a) x -> Sum a #

Generic (Product a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Product a) :: Type -> Type #

Methods

from :: Product a -> Rep (Product a) x #

to :: Rep (Product a) x -> Product a #

Generic (Down a)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Down a) :: Type -> Type #

Methods

from :: Down a -> Rep (Down a) x #

to :: Rep (Down a) x -> Down a #

Generic (NonEmpty a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (NonEmpty a) :: Type -> Type #

Methods

from :: NonEmpty a -> Rep (NonEmpty a) x #

to :: Rep (NonEmpty a) x -> NonEmpty a #

Generic (Tree a)

Since: containers-0.5.8

Instance details

Defined in Data.Tree

Associated Types

type Rep (Tree a) :: Type -> Type #

Methods

from :: Tree a -> Rep (Tree a) x #

to :: Rep (Tree a) x -> Tree a #

Generic (FingerTree a)

Since: containers-0.6.1

Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (FingerTree a) :: Type -> Type #

Methods

from :: FingerTree a -> Rep (FingerTree a) x #

to :: Rep (FingerTree a) x -> FingerTree a #

Generic (Digit a)

Since: containers-0.6.1

Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Digit a) :: Type -> Type #

Methods

from :: Digit a -> Rep (Digit a) x #

to :: Rep (Digit a) x -> Digit a #

Generic (Node a)

Since: containers-0.6.1

Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Node a) :: Type -> Type #

Methods

from :: Node a -> Rep (Node a) x #

to :: Rep (Node a) x -> Node a #

Generic (Elem a)

Since: containers-0.6.1

Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Elem a) :: Type -> Type #

Methods

from :: Elem a -> Rep (Elem a) x #

to :: Rep (Elem a) x -> Elem a #

Generic (ViewL a)

Since: containers-0.5.8

Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (ViewL a) :: Type -> Type #

Methods

from :: ViewL a -> Rep (ViewL a) x #

to :: Rep (ViewL a) x -> ViewL a #

Generic (ViewR a)

Since: containers-0.5.8

Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (ViewR a) :: Type -> Type #

Methods

from :: ViewR a -> Rep (ViewR a) x #

to :: Rep (ViewR a) x -> ViewR a #

Generic a => Generic (Generically a) 
Instance details

Defined in Generic.Data.Internal.Generically

Associated Types

type Rep (Generically a) :: Type -> Type #

Methods

from :: Generically a -> Rep (Generically a) x #

to :: Rep (Generically a) x -> Generically a #

Generic a => Generic (FiniteEnumeration a) 
Instance details

Defined in Generic.Data.Internal.Generically

Associated Types

type Rep (FiniteEnumeration a) :: Type -> Type #

Generic a => Generic (GenericProduct a) 
Instance details

Defined in Generic.Data.Internal.Generically

Associated Types

type Rep (GenericProduct a) :: Type -> Type #

Generic (ModuleName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ModuleName l) :: Type -> Type #

Methods

from :: ModuleName l -> Rep (ModuleName l) x #

to :: Rep (ModuleName l) x -> ModuleName l #

Generic (SpecialCon l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (SpecialCon l) :: Type -> Type #

Methods

from :: SpecialCon l -> Rep (SpecialCon l) x #

to :: Rep (SpecialCon l) x -> SpecialCon l #

Generic (QName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (QName l) :: Type -> Type #

Methods

from :: QName l -> Rep (QName l) x #

to :: Rep (QName l) x -> QName l #

Generic (Name l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Name l) :: Type -> Type #

Methods

from :: Name l -> Rep (Name l) x #

to :: Rep (Name l) x -> Name l #

Generic (IPName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (IPName l) :: Type -> Type #

Methods

from :: IPName l -> Rep (IPName l) x #

to :: Rep (IPName l) x -> IPName l #

Generic (QOp l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (QOp l) :: Type -> Type #

Methods

from :: QOp l -> Rep (QOp l) x #

to :: Rep (QOp l) x -> QOp l #

Generic (Op l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Op l) :: Type -> Type #

Methods

from :: Op l -> Rep (Op l) x #

to :: Rep (Op l) x -> Op l #

Generic (CName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (CName l) :: Type -> Type #

Methods

from :: CName l -> Rep (CName l) x #

to :: Rep (CName l) x -> CName l #

Generic (Module l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Module l) :: Type -> Type #

Methods

from :: Module l -> Rep (Module l) x #

to :: Rep (Module l) x -> Module l #

Generic (ModuleHead l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ModuleHead l) :: Type -> Type #

Methods

from :: ModuleHead l -> Rep (ModuleHead l) x #

to :: Rep (ModuleHead l) x -> ModuleHead l #

Generic (ExportSpecList l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ExportSpecList l) :: Type -> Type #

Generic (ExportSpec l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ExportSpec l) :: Type -> Type #

Methods

from :: ExportSpec l -> Rep (ExportSpec l) x #

to :: Rep (ExportSpec l) x -> ExportSpec l #

Generic (EWildcard l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (EWildcard l) :: Type -> Type #

Methods

from :: EWildcard l -> Rep (EWildcard l) x #

to :: Rep (EWildcard l) x -> EWildcard l #

Generic (Namespace l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Namespace l) :: Type -> Type #

Methods

from :: Namespace l -> Rep (Namespace l) x #

to :: Rep (Namespace l) x -> Namespace l #

Generic (ImportDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ImportDecl l) :: Type -> Type #

Methods

from :: ImportDecl l -> Rep (ImportDecl l) x #

to :: Rep (ImportDecl l) x -> ImportDecl l #

Generic (ImportSpecList l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ImportSpecList l) :: Type -> Type #

Generic (ImportSpec l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ImportSpec l) :: Type -> Type #

Methods

from :: ImportSpec l -> Rep (ImportSpec l) x #

to :: Rep (ImportSpec l) x -> ImportSpec l #

Generic (Assoc l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Assoc l) :: Type -> Type #

Methods

from :: Assoc l -> Rep (Assoc l) x #

to :: Rep (Assoc l) x -> Assoc l #

Generic (Decl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Decl l) :: Type -> Type #

Methods

from :: Decl l -> Rep (Decl l) x #

to :: Rep (Decl l) x -> Decl l #

Generic (PatternSynDirection l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (PatternSynDirection l) :: Type -> Type #

Generic (TypeEqn l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (TypeEqn l) :: Type -> Type #

Methods

from :: TypeEqn l -> Rep (TypeEqn l) x #

to :: Rep (TypeEqn l) x -> TypeEqn l #

Generic (Annotation l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Annotation l) :: Type -> Type #

Methods

from :: Annotation l -> Rep (Annotation l) x #

to :: Rep (Annotation l) x -> Annotation l #

Generic (BooleanFormula l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (BooleanFormula l) :: Type -> Type #

Generic (Role l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Role l) :: Type -> Type #

Methods

from :: Role l -> Rep (Role l) x #

to :: Rep (Role l) x -> Role l #

Generic (DataOrNew l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (DataOrNew l) :: Type -> Type #

Methods

from :: DataOrNew l -> Rep (DataOrNew l) x #

to :: Rep (DataOrNew l) x -> DataOrNew l #

Generic (InjectivityInfo l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (InjectivityInfo l) :: Type -> Type #

Generic (ResultSig l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ResultSig l) :: Type -> Type #

Methods

from :: ResultSig l -> Rep (ResultSig l) x #

to :: Rep (ResultSig l) x -> ResultSig l #

Generic (DeclHead l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (DeclHead l) :: Type -> Type #

Methods

from :: DeclHead l -> Rep (DeclHead l) x #

to :: Rep (DeclHead l) x -> DeclHead l #

Generic (InstRule l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (InstRule l) :: Type -> Type #

Methods

from :: InstRule l -> Rep (InstRule l) x #

to :: Rep (InstRule l) x -> InstRule l #

Generic (InstHead l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (InstHead l) :: Type -> Type #

Methods

from :: InstHead l -> Rep (InstHead l) x #

to :: Rep (InstHead l) x -> InstHead l #

Generic (Deriving l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Deriving l) :: Type -> Type #

Methods

from :: Deriving l -> Rep (Deriving l) x #

to :: Rep (Deriving l) x -> Deriving l #

Generic (DerivStrategy l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (DerivStrategy l) :: Type -> Type #

Generic (Binds l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Binds l) :: Type -> Type #

Methods

from :: Binds l -> Rep (Binds l) x #

to :: Rep (Binds l) x -> Binds l #

Generic (IPBind l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (IPBind l) :: Type -> Type #

Methods

from :: IPBind l -> Rep (IPBind l) x #

to :: Rep (IPBind l) x -> IPBind l #

Generic (Match l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Match l) :: Type -> Type #

Methods

from :: Match l -> Rep (Match l) x #

to :: Rep (Match l) x -> Match l #

Generic (QualConDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (QualConDecl l) :: Type -> Type #

Methods

from :: QualConDecl l -> Rep (QualConDecl l) x #

to :: Rep (QualConDecl l) x -> QualConDecl l #

Generic (ConDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ConDecl l) :: Type -> Type #

Methods

from :: ConDecl l -> Rep (ConDecl l) x #

to :: Rep (ConDecl l) x -> ConDecl l #

Generic (FieldDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (FieldDecl l) :: Type -> Type #

Methods

from :: FieldDecl l -> Rep (FieldDecl l) x #

to :: Rep (FieldDecl l) x -> FieldDecl l #

Generic (GadtDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (GadtDecl l) :: Type -> Type #

Methods

from :: GadtDecl l -> Rep (GadtDecl l) x #

to :: Rep (GadtDecl l) x -> GadtDecl l #

Generic (ClassDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ClassDecl l) :: Type -> Type #

Methods

from :: ClassDecl l -> Rep (ClassDecl l) x #

to :: Rep (ClassDecl l) x -> ClassDecl l #

Generic (InstDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (InstDecl l) :: Type -> Type #

Methods

from :: InstDecl l -> Rep (InstDecl l) x #

to :: Rep (InstDecl l) x -> InstDecl l #

Generic (BangType l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (BangType l) :: Type -> Type #

Methods

from :: BangType l -> Rep (BangType l) x #

to :: Rep (BangType l) x -> BangType l #

Generic (Unpackedness l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Unpackedness l) :: Type -> Type #

Methods

from :: Unpackedness l -> Rep (Unpackedness l) x #

to :: Rep (Unpackedness l) x -> Unpackedness l #

Generic (Rhs l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Rhs l) :: Type -> Type #

Methods

from :: Rhs l -> Rep (Rhs l) x #

to :: Rep (Rhs l) x -> Rhs l #

Generic (GuardedRhs l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (GuardedRhs l) :: Type -> Type #

Methods

from :: GuardedRhs l -> Rep (GuardedRhs l) x #

to :: Rep (GuardedRhs l) x -> GuardedRhs l #

Generic (Type l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Type l) :: Type -> Type #

Methods

from :: Type l -> Rep (Type l) x #

to :: Rep (Type l) x -> Type l #

Generic (MaybePromotedName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (MaybePromotedName l) :: Type -> Type #

Generic (Promoted l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Promoted l) :: Type -> Type #

Methods

from :: Promoted l -> Rep (Promoted l) x #

to :: Rep (Promoted l) x -> Promoted l #

Generic (TyVarBind l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (TyVarBind l) :: Type -> Type #

Methods

from :: TyVarBind l -> Rep (TyVarBind l) x #

to :: Rep (TyVarBind l) x -> TyVarBind l #

Generic (FunDep l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (FunDep l) :: Type -> Type #

Methods

from :: FunDep l -> Rep (FunDep l) x #

to :: Rep (FunDep l) x -> FunDep l #

Generic (Context l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Context l) :: Type -> Type #

Methods

from :: Context l -> Rep (Context l) x #

to :: Rep (Context l) x -> Context l #

Generic (Asst l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Asst l) :: Type -> Type #

Methods

from :: Asst l -> Rep (Asst l) x #

to :: Rep (Asst l) x -> Asst l #

Generic (Literal l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Literal l) :: Type -> Type #

Methods

from :: Literal l -> Rep (Literal l) x #

to :: Rep (Literal l) x -> Literal l #

Generic (Sign l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Sign l) :: Type -> Type #

Methods

from :: Sign l -> Rep (Sign l) x #

to :: Rep (Sign l) x -> Sign l #

Generic (Exp l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Exp l) :: Type -> Type #

Methods

from :: Exp l -> Rep (Exp l) x #

to :: Rep (Exp l) x -> Exp l #

Generic (XName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (XName l) :: Type -> Type #

Methods

from :: XName l -> Rep (XName l) x #

to :: Rep (XName l) x -> XName l #

Generic (XAttr l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (XAttr l) :: Type -> Type #

Methods

from :: XAttr l -> Rep (XAttr l) x #

to :: Rep (XAttr l) x -> XAttr l #

Generic (Bracket l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Bracket l) :: Type -> Type #

Methods

from :: Bracket l -> Rep (Bracket l) x #

to :: Rep (Bracket l) x -> Bracket l #

Generic (Splice l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Splice l) :: Type -> Type #

Methods

from :: Splice l -> Rep (Splice l) x #

to :: Rep (Splice l) x -> Splice l #

Generic (Safety l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Safety l) :: Type -> Type #

Methods

from :: Safety l -> Rep (Safety l) x #

to :: Rep (Safety l) x -> Safety l #

Generic (CallConv l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (CallConv l) :: Type -> Type #

Methods

from :: CallConv l -> Rep (CallConv l) x #

to :: Rep (CallConv l) x -> CallConv l #

Generic (ModulePragma l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ModulePragma l) :: Type -> Type #

Methods

from :: ModulePragma l -> Rep (ModulePragma l) x #

to :: Rep (ModulePragma l) x -> ModulePragma l #

Generic (Overlap l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Overlap l) :: Type -> Type #

Methods

from :: Overlap l -> Rep (Overlap l) x #

to :: Rep (Overlap l) x -> Overlap l #

Generic (Activation l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Activation l) :: Type -> Type #

Methods

from :: Activation l -> Rep (Activation l) x #

to :: Rep (Activation l) x -> Activation l #

Generic (Rule l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Rule l) :: Type -> Type #

Methods

from :: Rule l -> Rep (Rule l) x #

to :: Rep (Rule l) x -> Rule l #

Generic (RuleVar l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (RuleVar l) :: Type -> Type #

Methods

from :: RuleVar l -> Rep (RuleVar l) x #

to :: Rep (RuleVar l) x -> RuleVar l #

Generic (WarningText l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (WarningText l) :: Type -> Type #

Methods

from :: WarningText l -> Rep (WarningText l) x #

to :: Rep (WarningText l) x -> WarningText l #

Generic (Pat l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Pat l) :: Type -> Type #

Methods

from :: Pat l -> Rep (Pat l) x #

to :: Rep (Pat l) x -> Pat l #

Generic (PXAttr l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (PXAttr l) :: Type -> Type #

Methods

from :: PXAttr l -> Rep (PXAttr l) x #

to :: Rep (PXAttr l) x -> PXAttr l #

Generic (RPatOp l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (RPatOp l) :: Type -> Type #

Methods

from :: RPatOp l -> Rep (RPatOp l) x #

to :: Rep (RPatOp l) x -> RPatOp l #

Generic (RPat l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (RPat l) :: Type -> Type #

Methods

from :: RPat l -> Rep (RPat l) x #

to :: Rep (RPat l) x -> RPat l #

Generic (PatField l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (PatField l) :: Type -> Type #

Methods

from :: PatField l -> Rep (PatField l) x #

to :: Rep (PatField l) x -> PatField l #

Generic (Stmt l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Stmt l) :: Type -> Type #

Methods

from :: Stmt l -> Rep (Stmt l) x #

to :: Rep (Stmt l) x -> Stmt l #

Generic (QualStmt l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (QualStmt l) :: Type -> Type #

Methods

from :: QualStmt l -> Rep (QualStmt l) x #

to :: Rep (QualStmt l) x -> QualStmt l #

Generic (FieldUpdate l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (FieldUpdate l) :: Type -> Type #

Methods

from :: FieldUpdate l -> Rep (FieldUpdate l) x #

to :: Rep (FieldUpdate l) x -> FieldUpdate l #

Generic (Alt l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Alt l) :: Type -> Type #

Methods

from :: Alt l -> Rep (Alt l) x #

to :: Rep (Alt l) x -> Alt l #

Generic (Loc a) 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Associated Types

type Rep (Loc a) :: Type -> Type #

Methods

from :: Loc a -> Rep (Loc a) x #

to :: Rep (Loc a) x -> Loc a #

Generic (HistoriedResponse body) 
Instance details

Defined in Network.HTTP.Client

Associated Types

type Rep (HistoriedResponse body) :: Type -> Type #

Methods

from :: HistoriedResponse body -> Rep (HistoriedResponse body) x #

to :: Rep (HistoriedResponse body) x -> HistoriedResponse body #

Generic (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep (Doc a) :: Type -> Type #

Methods

from :: Doc a -> Rep (Doc a) x #

to :: Rep (Doc a) x -> Doc a #

Generic (Either a b)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Either a b) :: Type -> Type #

Methods

from :: Either a b -> Rep (Either a b) x #

to :: Rep (Either a b) x -> Either a b #

Generic (V1 p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (V1 p) :: Type -> Type #

Methods

from :: V1 p -> Rep (V1 p) x #

to :: Rep (V1 p) x -> V1 p #

Generic (U1 p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (U1 p) :: Type -> Type #

Methods

from :: U1 p -> Rep (U1 p) x #

to :: Rep (U1 p) x -> U1 p #

Generic (a, b)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b) :: Type -> Type #

Methods

from :: (a, b) -> Rep (a, b) x #

to :: Rep (a, b) x -> (a, b) #

Generic (Arg a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Arg a b) :: Type -> Type #

Methods

from :: Arg a b -> Rep (Arg a b) x #

to :: Rep (Arg a b) x -> Arg a b #

Generic (WrappedMonad m a)

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

Associated Types

type Rep (WrappedMonad m a) :: Type -> Type #

Methods

from :: WrappedMonad m a -> Rep (WrappedMonad m a) x #

to :: Rep (WrappedMonad m a) x -> WrappedMonad m a #

Generic (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: Type -> Type #

Methods

from :: Proxy t -> Rep (Proxy t) x #

to :: Rep (Proxy t) x -> Proxy t #

Generic (Cofree f a) 
Instance details

Defined in Control.Comonad.Cofree

Associated Types

type Rep (Cofree f a) :: Type -> Type #

Methods

from :: Cofree f a -> Rep (Cofree f a) x #

to :: Rep (Cofree f a) x -> Cofree f a #

Generic (Free f a) 
Instance details

Defined in Control.Monad.Free

Associated Types

type Rep (Free f a) :: Type -> Type #

Methods

from :: Free f a -> Rep (Free f a) x #

to :: Rep (Free f a) x -> Free f a #

Generic (f a) => Generic (Generically1 f a) 
Instance details

Defined in Generic.Data.Internal.Generically

Associated Types

type Rep (Generically1 f a) :: Type -> Type #

Methods

from :: Generically1 f a -> Rep (Generically1 f a) x #

to :: Rep (Generically1 f a) x -> Generically1 f a #

Generic (Rec1 f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Rec1 f p) :: Type -> Type #

Methods

from :: Rec1 f p -> Rep (Rec1 f p) x #

to :: Rep (Rec1 f p) x -> Rec1 f p #

Generic (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec (Ptr ()) p) :: Type -> Type #

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x #

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p #

Generic (URec Char p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Char p) :: Type -> Type #

Methods

from :: URec Char p -> Rep (URec Char p) x #

to :: Rep (URec Char p) x -> URec Char p #

Generic (URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Double p) :: Type -> Type #

Methods

from :: URec Double p -> Rep (URec Double p) x #

to :: Rep (URec Double p) x -> URec Double p #

Generic (URec Float p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Float p) :: Type -> Type #

Methods

from :: URec Float p -> Rep (URec Float p) x #

to :: Rep (URec Float p) x -> URec Float p #

Generic (URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Int p) :: Type -> Type #

Methods

from :: URec Int p -> Rep (URec Int p) x #

to :: Rep (URec Int p) x -> URec Int p #

Generic (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Word p) :: Type -> Type #

Methods

from :: URec Word p -> Rep (URec Word p) x #

to :: Rep (URec Word p) x -> URec Word p #

Generic (a, b, c)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c) :: Type -> Type #

Methods

from :: (a, b, c) -> Rep (a, b, c) x #

to :: Rep (a, b, c) x -> (a, b, c) #

Generic (WrappedArrow a b c)

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

Associated Types

type Rep (WrappedArrow a b c) :: Type -> Type #

Methods

from :: WrappedArrow a b c -> Rep (WrappedArrow a b c) x #

to :: Rep (WrappedArrow a b c) x -> WrappedArrow a b c #

Generic (Kleisli m a b)

Since: base-4.14.0.0

Instance details

Defined in Control.Arrow

Associated Types

type Rep (Kleisli m a b) :: Type -> Type #

Methods

from :: Kleisli m a b -> Rep (Kleisli m a b) x #

to :: Rep (Kleisli m a b) x -> Kleisli m a b #

Generic (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Associated Types

type Rep (Const a b) :: Type -> Type #

Methods

from :: Const a b -> Rep (Const a b) x #

to :: Rep (Const a b) x -> Const a b #

Generic (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Associated Types

type Rep (Ap f a) :: Type -> Type #

Methods

from :: Ap f a -> Rep (Ap f a) x #

to :: Rep (Ap f a) x -> Ap f a #

Generic (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Alt f a) :: Type -> Type #

Methods

from :: Alt f a -> Rep (Alt f a) x #

to :: Rep (Alt f a) x -> Alt f a #

Generic (Join p a) 
Instance details

Defined in Data.Bifunctor.Join

Associated Types

type Rep (Join p a) :: Type -> Type #

Methods

from :: Join p a -> Rep (Join p a) x #

to :: Rep (Join p a) x -> Join p a #

Generic (Fix p a) 
Instance details

Defined in Data.Bifunctor.Fix

Associated Types

type Rep (Fix p a) :: Type -> Type #

Methods

from :: Fix p a -> Rep (Fix p a) x #

to :: Rep (Fix p a) x -> Fix p a #

Generic (FreeF f a b) 
Instance details

Defined in Control.Monad.Trans.Free

Associated Types

type Rep (FreeF f a b) :: Type -> Type #

Methods

from :: FreeF f a b -> Rep (FreeF f a b) x #

to :: Rep (FreeF f a b) x -> FreeF f a b #

Generic (CofreeF f a b) 
Instance details

Defined in Control.Comonad.Trans.Cofree

Associated Types

type Rep (CofreeF f a b) :: Type -> Type #

Methods

from :: CofreeF f a b -> Rep (CofreeF f a b) x #

to :: Rep (CofreeF f a b) x -> CofreeF f a b #

Generic (Tagged s b) 
Instance details

Defined in Data.Tagged

Associated Types

type Rep (Tagged s b) :: Type -> Type #

Methods

from :: Tagged s b -> Rep (Tagged s b) x #

to :: Rep (Tagged s b) x -> Tagged s b #

Generic (K1 i c p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (K1 i c p) :: Type -> Type #

Methods

from :: K1 i c p -> Rep (K1 i c p) x #

to :: Rep (K1 i c p) x -> K1 i c p #

Generic ((f :+: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :+: g) p) :: Type -> Type #

Methods

from :: (f :+: g) p -> Rep ((f :+: g) p) x #

to :: Rep ((f :+: g) p) x -> (f :+: g) p #

Generic ((f :*: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :*: g) p) :: Type -> Type #

Methods

from :: (f :*: g) p -> Rep ((f :*: g) p) x #

to :: Rep ((f :*: g) p) x -> (f :*: g) p #

Generic (a, b, c, d)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d) :: Type -> Type #

Methods

from :: (a, b, c, d) -> Rep (a, b, c, d) x #

to :: Rep (a, b, c, d) x -> (a, b, c, d) #

Generic (Product f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Associated Types

type Rep (Product f g a) :: Type -> Type #

Methods

from :: Product f g a -> Rep (Product f g a) x #

to :: Rep (Product f g a) x -> Product f g a #

Generic (Sum f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Associated Types

type Rep (Sum f g a) :: Type -> Type #

Methods

from :: Sum f g a -> Rep (Sum f g a) x #

to :: Rep (Sum f g a) x -> Sum f g a #

Generic (M1 i c f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (M1 i c f p) :: Type -> Type #

Methods

from :: M1 i c f p -> Rep (M1 i c f p) x #

to :: Rep (M1 i c f p) x -> M1 i c f p #

Generic ((f :.: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :.: g) p) :: Type -> Type #

Methods

from :: (f :.: g) p -> Rep ((f :.: g) p) x #

to :: Rep ((f :.: g) p) x -> (f :.: g) p #

Generic (a, b, c, d, e)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e) :: Type -> Type #

Methods

from :: (a, b, c, d, e) -> Rep (a, b, c, d, e) x #

to :: Rep (a, b, c, d, e) x -> (a, b, c, d, e) #

Generic (Compose f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Associated Types

type Rep (Compose f g a) :: Type -> Type #

Methods

from :: Compose f g a -> Rep (Compose f g a) x #

to :: Rep (Compose f g a) x -> Compose f g a #

Generic (WrappedBifunctor p a b) 
Instance details

Defined in Data.Bifunctor.Wrapped

Associated Types

type Rep (WrappedBifunctor p a b) :: Type -> Type #

Methods

from :: WrappedBifunctor p a b -> Rep (WrappedBifunctor p a b) x #

to :: Rep (WrappedBifunctor p a b) x -> WrappedBifunctor p a b #

Generic (Joker g a b) 
Instance details

Defined in Data.Bifunctor.Joker

Associated Types

type Rep (Joker g a b) :: Type -> Type #

Methods

from :: Joker g a b -> Rep (Joker g a b) x #

to :: Rep (Joker g a b) x -> Joker g a b #

Generic (Flip p a b) 
Instance details

Defined in Data.Bifunctor.Flip

Associated Types

type Rep (Flip p a b) :: Type -> Type #

Methods

from :: Flip p a b -> Rep (Flip p a b) x #

to :: Rep (Flip p a b) x -> Flip p a b #

Generic (Clown f a b) 
Instance details

Defined in Data.Bifunctor.Clown

Associated Types

type Rep (Clown f a b) :: Type -> Type #

Methods

from :: Clown f a b -> Rep (Clown f a b) x #

to :: Rep (Clown f a b) x -> Clown f a b #

Generic (a, b, c, d, e, f)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f) -> Rep (a, b, c, d, e, f) x #

to :: Rep (a, b, c, d, e, f) x -> (a, b, c, d, e, f) #

Generic (Sum p q a b) 
Instance details

Defined in Data.Bifunctor.Sum

Associated Types

type Rep (Sum p q a b) :: Type -> Type #

Methods

from :: Sum p q a b -> Rep (Sum p q a b) x #

to :: Rep (Sum p q a b) x -> Sum p q a b #

Generic (Product f g a b) 
Instance details

Defined in Data.Bifunctor.Product

Associated Types

type Rep (Product f g a b) :: Type -> Type #

Methods

from :: Product f g a b -> Rep (Product f g a b) x #

to :: Rep (Product f g a b) x -> Product f g a b #

Generic (a, b, c, d, e, f, g)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g) -> Rep (a, b, c, d, e, f, g) x #

to :: Rep (a, b, c, d, e, f, g) x -> (a, b, c, d, e, f, g) #

Generic (Tannen f p a b) 
Instance details

Defined in Data.Bifunctor.Tannen

Associated Types

type Rep (Tannen f p a b) :: Type -> Type #

Methods

from :: Tannen f p a b -> Rep (Tannen f p a b) x #

to :: Rep (Tannen f p a b) x -> Tannen f p a b #

Generic (Biff p f g a b) 
Instance details

Defined in Data.Bifunctor.Biff

Associated Types

type Rep (Biff p f g a b) :: Type -> Type #

Methods

from :: Biff p f g a b -> Rep (Biff p f g a b) x #

to :: Rep (Biff p f g a b) x -> Biff p f g a b #

pathInfoInverse_prop :: (Eq url, PathInfo url) => url -> Bool #

test that a PathInfo instance is valid

Generates Arbitrary url values and checks that:

fromPathInfo . toPathInfo == id

mkSitePI #

Arguments

:: PathInfo url 
=> ((url -> [(Text, Maybe Text)] -> Text) -> url -> a)

a routing function

-> Site url a 

turn a routing function into a Site value using the PathInfo class

fromPathInfoParams :: PathInfo url => ByteString -> Either String (url, [(Text, Maybe Text)]) #

parse a String into '(url, Query)' using PathInfo.

returns Left "parse error" on failure

returns Right (url, Query on success

fromPathInfo :: PathInfo url => ByteString -> Either String url #

parse a String into url using PathInfo.

returns Left "parse error" on failure

returns Right url on success

toPathInfoParams #

Arguments

:: PathInfo url 
=> url

url

-> [(Text, Maybe Text)]

query string parameter

-> Text 

convert url + params into the path info portion of a URL + a query string

toPathInfo :: PathInfo url => url -> Text #

convert url into the path info portion of a URL

parseSegments :: URLParser a -> [Text] -> Either String a #

run a URLParser on a list of path segments

returns Left "parse error" on failure.

returns Right a on success

showParseError :: ParseError -> String #

show Parsec ParseError using terms that relevant to parsing a url

patternParse :: ([Text] -> Either String a) -> URLParser a #

apply a function to the remainder of the segments

useful if you want to just do normal pattern matching: > > foo ["foo", "bar"] = Right (Foo Bar) > foo ["baz"] = Right Baz > foo _ = Left "parse error"

patternParse foo

anySegment :: URLParser Text #

match on any string

segment :: Text -> URLParser Text #

match on a specific string

pToken :: tok -> (Text -> Maybe a) -> URLParser a #

stripOverlap :: Eq a => [a] -> [a] -> [a] #

type URLParser a = GenParser Text () a #

class PathInfo url where #

Simple parsing and rendering for a type to and from URL path segments.

If you're using GHC 7.2 or later, you can use DeriveGeneric to derive instances of this class:

{-# LANGUAGE DeriveGeneric #-}
data Sitemap = Home | BlogPost Int deriving Generic
instance PathInfo Sitemap

This results in the following instance:

instance PathInfo Sitemap where
    toPathSegments Home = ["home"]
    toPathSegments (BlogPost x) = "blog-post" : toPathSegments x
    fromPathSegments = Home <$ segment "home"
                   <|> BlogPost <$ segment "blog-post" <*> fromPathSegments

And here it is in action:

>>> toPathInfo (BlogPost 123)
"/blog-post/123"
>>> fromPathInfo "/blog-post/123" :: Either String Sitemap
Right (BlogPost 123)

To instead derive instances using TemplateHaskell, see web-routes-th.

Minimal complete definition

Nothing

Methods

toPathSegments :: url -> [Text] #

fromPathSegments :: URLParser url #

Instances

Instances details
PathInfo Int 
Instance details

Defined in Web.Routes.PathInfo

PathInfo Int64 
Instance details

Defined in Web.Routes.PathInfo

PathInfo Integer 
Instance details

Defined in Web.Routes.PathInfo

PathInfo String 
Instance details

Defined in Web.Routes.PathInfo

PathInfo Text 
Instance details

Defined in Web.Routes.PathInfo

PathInfo PasswordURL 
Instance details

Defined in Happstack.Authenticate.Password.URL

PathInfo AccountURL 
Instance details

Defined in Happstack.Authenticate.Password.URL

PathInfo PartialURL 
Instance details

Defined in Happstack.Authenticate.Password.PartialsURL

PathInfo OpenIdURL 
Instance details

Defined in Happstack.Authenticate.OpenId.URL

PathInfo PartialURL 
Instance details

Defined in Happstack.Authenticate.OpenId.PartialsURL

PathInfo AuthenticateURL 
Instance details

Defined in Happstack.Authenticate.Core

PathInfo AuthenticationMethod 
Instance details

Defined in Happstack.Authenticate.Core

PathInfo Email 
Instance details

Defined in Happstack.Authenticate.Core

PathInfo Username 
Instance details

Defined in Happstack.Authenticate.Core

PathInfo UserId 
Instance details

Defined in Data.UserId

PathInfo AdminURL Source # 
Instance details

Defined in Clckwrks.Admin.URL

PathInfo AuthURL Source # 
Instance details

Defined in Clckwrks.Authenticate.URL

PathInfo JSURL Source # 
Instance details

Defined in Clckwrks.JS.URL

PathInfo ProfileDataURL Source # 
Instance details

Defined in Clckwrks.ProfileData.URL

PathInfo ClckURL Source # 
Instance details

Defined in Clckwrks.URL

PathInfo [String] 
Instance details

Defined in Web.Routes.PathInfo

PathInfo [Text] 
Instance details

Defined in Web.Routes.PathInfo

PathInfo (NoEscape String) Source # 
Instance details

Defined in Clckwrks.URL

runSite #

Arguments

:: Text

application root, with trailing slash

-> Site url a 
-> [Text]

path info, (call decodePathInfo on path with leading slash stripped)

-> Either String a 

Retrieve the application to handle a given request.

NOTE: use decodePathInfo to convert a ByteString url to a properly decoded list of path segments

setDefault :: url -> Site url a -> Site url a #

Override the "default" URL, ie the result of parsePathSegments [].

data Site url a #

A site groups together the three functions necesary to make an application:

  • A function to convert from the URL type to path segments.
  • A function to convert from path segments to the URL, if possible.
  • A function to return the application for a given URL.

There are two type parameters for Site: the first is the URL datatype, the second is the application datatype. The application datatype will depend upon your server backend.

Constructors

Site 

Fields

Instances

Instances details
Functor (Site url) 
Instance details

Defined in Web.Routes.Site

Methods

fmap :: (a -> b) -> Site url a -> Site url b #

(<$) :: a -> Site url b -> Site url a #

showURLParams :: MonadRoute m => URL m -> [(Text, Maybe Text)] -> m Text #

showURL :: MonadRoute m => URL m -> m Text #

askRouteT :: forall (m :: Type -> Type) url. Monad m => RouteT url m (url -> [(Text, Maybe Text)] -> Text) #

liftRouteT :: m a -> RouteT url m a #

withRouteT :: forall url' url (m :: Type -> Type) a. ((url' -> [(Text, Maybe Text)] -> Text) -> url -> [(Text, Maybe Text)] -> Text) -> RouteT url m a -> RouteT url' m a #

Execute a computation in a modified environment

mapRouteT :: (m a -> n b) -> RouteT url m a -> RouteT url n b #

Transform the computation inside a RouteT.

runRouteT :: (url -> RouteT url m a) -> (url -> [(Text, Maybe Text)] -> Text) -> url -> m a #

convert a RouteT based route handler to a handler that can be used with the Site type

NOTE: this function used to be the same as unRouteT. If you want the old behavior, just call unRouteT.

newtype RouteT url (m :: Type -> Type) a #

monad transformer for generating URLs

Constructors

RouteT 

Fields

Instances

Instances details
MonadRWS r w s m => MonadRWS r w s (RouteT url m) 
Instance details

Defined in Web.Routes.RouteT

MonadReader r m => MonadReader r (RouteT url m) 
Instance details

Defined in Web.Routes.RouteT

Methods

ask :: RouteT url m r #

local :: (r -> r) -> RouteT url m a -> RouteT url m a #

reader :: (r -> a) -> RouteT url m a #

MonadState s m => MonadState s (RouteT url m) 
Instance details

Defined in Web.Routes.RouteT

Methods

get :: RouteT url m s #

put :: s -> RouteT url m () #

state :: (s -> (a, s)) -> RouteT url m a #

MonadError e m => MonadError e (RouteT url m) 
Instance details

Defined in Web.Routes.RouteT

Methods

throwError :: e -> RouteT url m a #

catchError :: RouteT url m a -> (e -> RouteT url m a) -> RouteT url m a #

MonadWriter w m => MonadWriter w (RouteT url m) 
Instance details

Defined in Web.Routes.RouteT

Methods

writer :: (a, w) -> RouteT url m a #

tell :: w -> RouteT url m () #

listen :: RouteT url m a -> RouteT url m (a, w) #

pass :: RouteT url m (a, w -> w) -> RouteT url m a #

MonadTrans (RouteT url) 
Instance details

Defined in Web.Routes.RouteT

Methods

lift :: Monad m => m a -> RouteT url m a #

Monad m => Monad (RouteT url m) 
Instance details

Defined in Web.Routes.RouteT

Methods

(>>=) :: RouteT url m a -> (a -> RouteT url m b) -> RouteT url m b #

(>>) :: RouteT url m a -> RouteT url m b -> RouteT url m b #

return :: a -> RouteT url m a #

Functor m => Functor (RouteT url m) 
Instance details

Defined in Web.Routes.RouteT

Methods

fmap :: (a -> b) -> RouteT url m a -> RouteT url m b #

(<$) :: a -> RouteT url m b -> RouteT url m a #

MonadFix m => MonadFix (RouteT url m) 
Instance details

Defined in Web.Routes.RouteT

Methods

mfix :: (a -> RouteT url m a) -> RouteT url m a #

MonadFail m => MonadFail (RouteT url m) 
Instance details

Defined in Web.Routes.RouteT

Methods

fail :: String -> RouteT url m a #

Applicative m => Applicative (RouteT url m) 
Instance details

Defined in Web.Routes.RouteT

Methods

pure :: a -> RouteT url m a #

(<*>) :: RouteT url m (a -> b) -> RouteT url m a -> RouteT url m b #

liftA2 :: (a -> b -> c) -> RouteT url m a -> RouteT url m b -> RouteT url m c #

(*>) :: RouteT url m a -> RouteT url m b -> RouteT url m b #

(<*) :: RouteT url m a -> RouteT url m b -> RouteT url m a #

Alternative m => Alternative (RouteT url m) 
Instance details

Defined in Web.Routes.RouteT

Methods

empty :: RouteT url m a #

(<|>) :: RouteT url m a -> RouteT url m a -> RouteT url m a #

some :: RouteT url m a -> RouteT url m [a] #

many :: RouteT url m a -> RouteT url m [a] #

(MonadPlus m, Monad (RouteT url m)) => MonadPlus (RouteT url m) 
Instance details

Defined in Web.Routes.RouteT

Methods

mzero :: RouteT url m a #

mplus :: RouteT url m a -> RouteT url m a -> RouteT url m a #

MonadIO m => MonadIO (RouteT url m) 
Instance details

Defined in Web.Routes.RouteT

Methods

liftIO :: IO a -> RouteT url m a #

MonadThrow m => MonadThrow (RouteT url m) 
Instance details

Defined in Web.Routes.RouteT

Methods

throwM :: Exception e => e -> RouteT url m a #

MonadCatch m => MonadCatch (RouteT url m) 
Instance details

Defined in Web.Routes.RouteT

Methods

catch :: Exception e => RouteT url m a -> (e -> RouteT url m a) -> RouteT url m a #

MonadCont m => MonadCont (RouteT url m) 
Instance details

Defined in Web.Routes.RouteT

Methods

callCC :: ((a -> RouteT url m b) -> RouteT url m a) -> RouteT url m a #

Monad m => MonadRoute (RouteT url m) 
Instance details

Defined in Web.Routes.RouteT

Associated Types

type URL (RouteT url m) #

Methods

askRouteFn :: RouteT url m (URL (RouteT url m) -> [(Text, Maybe Text)] -> Text) #

newtype AttributeType (RouteT url m) 
Instance details

Defined in Web.Routes.XMLGenT

newtype AttributeType (RouteT url m) = UAttr {}
newtype ChildType (RouteT url m) 
Instance details

Defined in Web.Routes.XMLGenT

newtype ChildType (RouteT url m) = UChild {}
type StringType (RouteT url m) 
Instance details

Defined in Web.Routes.XMLGenT

type StringType (RouteT url m) = Text
type XMLType (RouteT url m) 
Instance details

Defined in Web.Routes.XMLGenT

type XMLType (RouteT url m) = XML
type URL (RouteT url m) 
Instance details

Defined in Web.Routes.RouteT

type URL (RouteT url m) = url

type family URL (m :: Type -> Type) #

Instances

Instances details
type URL (XMLGenT m) 
Instance details

Defined in Web.Routes.XMLGenT

type URL (XMLGenT m) = URL m
type URL (RouteT url m) 
Instance details

Defined in Web.Routes.RouteT

type URL (RouteT url m) = url
type URL (ClckT url m) Source # 
Instance details

Defined in Clckwrks.Monad

type URL (ClckT url m) = url

class Monad m => MonadRoute (m :: Type -> Type) where #

Associated Types

type URL (m :: Type -> Type) #

Methods

askRouteFn :: m (URL m -> [(Text, Maybe Text)] -> Text) #

Instances

Instances details
Monad m => MonadRoute (RouteT url m) 
Instance details

Defined in Web.Routes.RouteT

Associated Types

type URL (RouteT url m) #

Methods

askRouteFn :: RouteT url m (URL (RouteT url m) -> [(Text, Maybe Text)] -> Text) #

Monad m => MonadRoute (ClckT url m) Source # 
Instance details

Defined in Clckwrks.Monad

Associated Types

type URL (ClckT url m) #

Methods

askRouteFn :: ClckT url m (URL (ClckT url m) -> [(Text, Maybe Text)] -> Text) #

decodePathInfoParams :: ByteString -> ([Text], [(Text, Maybe Text)]) #

Returns path segments as well as possible query string components

For example:

decodePathInfoParams "/home?q=1"

(["home"],[("q",Just "1")])

decodePathInfo :: ByteString -> [Text] #

Performs the inverse operation of encodePathInfo.

In particular, this function:

  • Splits a string at each occurence of a forward slash.
  • Percent-decodes the individual pieces.
  • UTF-8 decodes the resulting data.

This utilizes decodeString from the utf8-string library, and thus all UTF-8 decoding errors are handled as per that library.

In general, you will want to strip the leading slash from a pathinfo before passing it to this function. For example:

decodePathInfo \"\"

[]

decodePathInfo \"\/\"
""

Note that while function accepts a Text value, it is expected that Text will only contain the subset of characters which are allowed to appear in a URL.

encodePathInfo :: [Text] -> [(Text, Maybe Text)] -> Text #

Encodes a list of path segments into a valid URL fragment.

This function takes the following three steps:

  • UTF-8 encodes the characters.
  • Performs percent encoding on all unreserved characters, as well as :@=+$,
  • Intercalates with a slash.

For example:

encodePathInfo [\"foo\", \"bar\", \"baz\"]

"foo/bar/baz"

encodePathInfo [\"foo bar\", \"baz\/bin\"]

"foo%20bar/baz%2Fbin"

encodePathInfo [\"שלום\"]

"%D7%A9%D7%9C%D7%95%D7%9D"

seeOtherURL :: (MonadRoute m, FilterMonad Response m) => URL m -> m Response #

similar to seeOther but takes a URL m as an argument