{-# LANGUAGE FlexibleInstances #-}
module Language.C.Quote.ObjC (
ToIdent(..),
ToConst(..),
ToExp(..),
objcLit,
cexp,
cedecl,
cdecl,
csdecl,
cenum,
ctyquals,
cty,
cparam,
cparams,
cinit,
cstm,
cstms,
citem,
citems,
cunit,
cfun,
objcprop,
objcifdecls,
objcimdecls,
objcdictelem,
objcpropattr,
objcmethparam,
objcmethproto,
objcmethdef,
objcmethrecv,
objcarg
) where
import qualified Language.C.Parser as P
import qualified Language.C.Syntax as C
import Language.C.Quote.Base (ToIdent(..), ToConst(..), ToExp(..), quasiquote)
import Language.Haskell.TH.Quote (QuasiQuoter)
exts :: [C.Extensions]
exts :: [Extensions]
exts = [Extensions
C.ObjC, Extensions
C.Blocks, Extensions
C.Gcc]
typenames :: [String]
typenames :: [String]
typenames = [String
"id", String
"instancetype"]
newtype ObjCLit a = ObjCLit a
deriving (Int -> ObjCLit a -> ShowS
forall a. Show a => Int -> ObjCLit a -> ShowS
forall a. Show a => [ObjCLit a] -> ShowS
forall a. Show a => ObjCLit a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ObjCLit a] -> ShowS
$cshowList :: forall a. Show a => [ObjCLit a] -> ShowS
show :: ObjCLit a -> String
$cshow :: forall a. Show a => ObjCLit a -> String
showsPrec :: Int -> ObjCLit a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> ObjCLit a -> ShowS
Show, ReadPrec [ObjCLit a]
ReadPrec (ObjCLit a)
ReadS [ObjCLit a]
forall a. Read a => ReadPrec [ObjCLit a]
forall a. Read a => ReadPrec (ObjCLit a)
forall a. Read a => Int -> ReadS (ObjCLit a)
forall a. Read a => ReadS [ObjCLit a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ObjCLit a]
$creadListPrec :: forall a. Read a => ReadPrec [ObjCLit a]
readPrec :: ReadPrec (ObjCLit a)
$creadPrec :: forall a. Read a => ReadPrec (ObjCLit a)
readList :: ReadS [ObjCLit a]
$creadList :: forall a. Read a => ReadS [ObjCLit a]
readsPrec :: Int -> ReadS (ObjCLit a)
$creadsPrec :: forall a. Read a => Int -> ReadS (ObjCLit a)
Read, ObjCLit a -> ObjCLit a -> Bool
forall a. Eq a => ObjCLit a -> ObjCLit a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjCLit a -> ObjCLit a -> Bool
$c/= :: forall a. Eq a => ObjCLit a -> ObjCLit a -> Bool
== :: ObjCLit a -> ObjCLit a -> Bool
$c== :: forall a. Eq a => ObjCLit a -> ObjCLit a -> Bool
Eq, ObjCLit a -> ObjCLit a -> Bool
ObjCLit a -> ObjCLit a -> Ordering
ObjCLit a -> ObjCLit a -> ObjCLit a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {a}. Ord a => Eq (ObjCLit a)
forall a. Ord a => ObjCLit a -> ObjCLit a -> Bool
forall a. Ord a => ObjCLit a -> ObjCLit a -> Ordering
forall a. Ord a => ObjCLit a -> ObjCLit a -> ObjCLit a
min :: ObjCLit a -> ObjCLit a -> ObjCLit a
$cmin :: forall a. Ord a => ObjCLit a -> ObjCLit a -> ObjCLit a
max :: ObjCLit a -> ObjCLit a -> ObjCLit a
$cmax :: forall a. Ord a => ObjCLit a -> ObjCLit a -> ObjCLit a
>= :: ObjCLit a -> ObjCLit a -> Bool
$c>= :: forall a. Ord a => ObjCLit a -> ObjCLit a -> Bool
> :: ObjCLit a -> ObjCLit a -> Bool
$c> :: forall a. Ord a => ObjCLit a -> ObjCLit a -> Bool
<= :: ObjCLit a -> ObjCLit a -> Bool
$c<= :: forall a. Ord a => ObjCLit a -> ObjCLit a -> Bool
< :: ObjCLit a -> ObjCLit a -> Bool
$c< :: forall a. Ord a => ObjCLit a -> ObjCLit a -> Bool
compare :: ObjCLit a -> ObjCLit a -> Ordering
$ccompare :: forall a. Ord a => ObjCLit a -> ObjCLit a -> Ordering
Ord)
instance ToExp (ObjCLit String) where
toExp :: ObjCLit String -> SrcLoc -> Exp
toExp (ObjCLit String
s) SrcLoc
loc = [Const] -> SrcLoc -> Exp
C.ObjCLitString [[String] -> String -> SrcLoc -> Const
C.StringConst [forall a. Show a => a -> String
show String
s] String
s SrcLoc
loc] SrcLoc
loc
instance ToExp (ObjCLit Bool) where
toExp :: ObjCLit Bool -> SrcLoc -> Exp
toExp (ObjCLit Bool
b) SrcLoc
loc = Bool -> SrcLoc -> Exp
C.ObjCLitBool Bool
b SrcLoc
loc
instance ToExp (ObjCLit Char) where
toExp :: ObjCLit Char -> SrcLoc -> Exp
toExp (ObjCLit Char
c) SrcLoc
loc = Maybe UnOp -> Const -> SrcLoc -> Exp
C.ObjCLitConst forall a. Maybe a
Nothing (String -> Char -> SrcLoc -> Const
C.CharConst (forall a. Show a => a -> String
show Char
c) Char
c SrcLoc
loc) SrcLoc
loc
objcLit :: a -> ObjCLit a
objcLit :: forall a. a -> ObjCLit a
objcLit = forall a. a -> ObjCLit a
ObjCLit
cdecl, cedecl, cenum, cexp, cfun, cinit, cparam, cparams, csdecl, cstm, cstms :: QuasiQuoter
citem, citems, ctyquals, cty, cunit :: QuasiQuoter
cdecl :: QuasiQuoter
cdecl = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P InitGroup
P.parseDecl
cedecl :: QuasiQuoter
cedecl = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P Definition
P.parseEdecl
cenum :: QuasiQuoter
cenum = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P CEnum
P.parseEnum
cexp :: QuasiQuoter
cexp = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P Exp
P.parseExp
cfun :: QuasiQuoter
cfun = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P Func
P.parseFunc
cinit :: QuasiQuoter
cinit = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P Initializer
P.parseInit
cparam :: QuasiQuoter
cparam = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P Param
P.parseParam
cparams :: QuasiQuoter
cparams = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P [Param]
P.parseParams
csdecl :: QuasiQuoter
csdecl = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P FieldGroup
P.parseStructDecl
cstm :: QuasiQuoter
cstm = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P Stm
P.parseStm
cstms :: QuasiQuoter
cstms = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P [Stm]
P.parseStms
citem :: QuasiQuoter
citem = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P BlockItem
P.parseBlockItem
citems :: QuasiQuoter
citems = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P [BlockItem]
P.parseBlockItems
ctyquals :: QuasiQuoter
ctyquals = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P [TypeQual]
P.parseTypeQuals
cty :: QuasiQuoter
cty = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P Type
P.parseType
cunit :: QuasiQuoter
cunit = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P [Definition]
P.parseUnit
objcprop, objcpropattr, objcifdecls, objcimdecls, objcdictelem, objcmethparam, objcmethproto :: QuasiQuoter
objcmethdef, objcmethrecv, objcarg :: QuasiQuoter
objcprop :: QuasiQuoter
objcprop = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P ObjCIfaceDecl
P.parseObjCProp
objcifdecls :: QuasiQuoter
objcifdecls = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P [ObjCIfaceDecl]
P.parseObjCIfaceDecls
objcimdecls :: QuasiQuoter
objcimdecls = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P [Definition]
P.parseObjCImplDecls
objcpropattr :: QuasiQuoter
objcpropattr = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P ObjCPropAttr
P.parseObjCPropAttr
objcdictelem :: QuasiQuoter
objcdictelem = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P ObjCDictElem
P.parseObjCDictElem
objcmethparam :: QuasiQuoter
objcmethparam = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P ObjCParam
P.parseObjCMethodParam
objcmethproto :: QuasiQuoter
objcmethproto = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P ObjCMethodProto
P.parseObjCMethodProto
objcmethdef :: QuasiQuoter
objcmethdef = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P Definition
P.parseObjCMethodDef
objcmethrecv :: QuasiQuoter
objcmethrecv = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P ObjCRecv
P.parseObjCMethodRecv
objcarg :: QuasiQuoter
objcarg = forall a. Data a => [Extensions] -> [String] -> P a -> QuasiQuoter
quasiquote [Extensions]
exts [String]
typenames P ObjCArg
P.parseObjCKeywordArg