Skip to content

Commit

Permalink
Add documentation for the Clang.USR module (formerly Clang.CrossRefer…
Browse files Browse the repository at this point in the history
…ence). #23
  • Loading branch information
sethfowler committed Apr 22, 2014
1 parent 092f155 commit 4534208
Show file tree
Hide file tree
Showing 4 changed files with 84 additions and 37 deletions.
2 changes: 1 addition & 1 deletion LibClang.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,6 @@ Library
exposed-modules: Clang,
Clang.Comment,
Clang.Completion,
Clang.CrossReference,
Clang.Cursor,
Clang.Debug,
Clang.Diagnostic,
Expand All @@ -67,6 +66,7 @@ Library
Clang.Token,
Clang.TranslationUnit,
Clang.Type,
Clang.USR,
Clang.Version
other-modules: Clang.Internal.BitFlags,
Clang.Internal.Monad,
Expand Down
36 changes: 0 additions & 36 deletions src/Clang/CrossReference.hs

This file was deleted.

4 changes: 4 additions & 0 deletions src/Clang/Cursor.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,7 @@ module Clang.Cursor
, getTypeDeclaration
, getNumArguments
, getArgument
, getUSR

-- attribute function
, getIBOutletCollectionType
Expand Down Expand Up @@ -204,6 +205,9 @@ getNumArguments c = liftIO $ FFI.cursor_getNumArguments c
getArgument :: ClangBase m => FFI.Cursor s' -> Int -> ClangT s m (FFI.Cursor s)
getArgument c i = liftIO $ FFI.cursor_getArgument mkProxy c i

getUSR :: ClangBase m => FFI.Cursor s' -> ClangT s m (FFI.ClangString s)
getUSR = FFI.getCursorUSR

-- attribute function

getIBOutletCollectionType :: ClangBase m => FFI.Cursor s' -> ClangT s m (FFI.Type s)
Expand Down
79 changes: 79 additions & 0 deletions src/Clang/USR.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,79 @@
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}

-- | Functions for manipulating 'Unified Symbol Resolution' values, or
-- \'USRs\'. USRs are strings that provide an unambiguous reference to a
-- symbol. Any two cursors that refer to the same semantic entity will
-- have the same USR, even if they occur in different translation
-- units. This is very useful when attempting to cross-reference
-- between different source files in a project.
--
-- Most often, using USRs simply means retrieving the USR that
-- corresponds to a 'Clang.Cursor'. You can do this using
-- 'Clang.Cursor.getUSR', and then convert to a Haskell string using
-- the functions in "Clang.String".
--
-- This module is intended to be imported qualified.
module Clang.USR
( createFromObjCClass
, createFromObjCCategory
, createFromObjCProtocol
, createFromObjCIvar
, createFromObjCInstanceMethod
, createFromObjCClassMethod
, createFromObjCProperty
) where

import qualified Clang.Internal.FFI as FFI
import Clang.Internal.Monad

-- | Construct a USR for the specified Objective-C class.
createFromObjCClass :: ClangBase m
=> String -- ^ A class name.
-> ClangT s m (FFI.ClangString s)
createFromObjCClass = FFI.constructUSR_ObjCClass

-- | Construct a USR for the specified Objective-C category.
createFromObjCCategory :: ClangBase m
=> String -- ^ A class name.
-> String -- ^ A category name.
-> ClangT s m (FFI.ClangString s)
createFromObjCCategory = FFI.constructUSR_ObjCCategory

-- | Construct a USR for the specified Objective-C protocol.
createFromObjCProtocol :: ClangBase m
=> String -- ^ A protocol name.
-> ClangT s m (FFI.ClangString s)
createFromObjCProtocol = FFI.constructUSR_ObjCProtocol

-- | Construct a USR for the specified Objective-C instance variable,
-- given the USR for its containing class.
createFromObjCIvar :: ClangBase m
=> String -- ^ An instance variable name.
-> FFI.ClangString s' -- ^ A class USR.
-> ClangT s m (FFI.ClangString s)
createFromObjCIvar = FFI.constructUSR_ObjCIvar

-- | Construct a USR for the specified Objective-C instance method, given the USR
-- for its containing class.
createFromObjCInstanceMethod :: ClangBase m
=> String -- ^ A method name.
-> FFI.ClangString s' -- ^ A class USR.
-> ClangT s m (FFI.ClangString s)
createFromObjCInstanceMethod name = FFI.constructUSR_ObjCMethod name True

-- | Construct a USR for the specified Objective-C class method, given the USR
-- for its containing class.
createFromObjCClassMethod :: ClangBase m
=> String -- ^ A method name.
-> FFI.ClangString s' -- ^ A class USR.
-> ClangT s m (FFI.ClangString s)
createFromObjCClassMethod name = FFI.constructUSR_ObjCMethod name False

-- | Construct a USR for the specified Objective-C property, given the USR
-- for its containing class.
createFromObjCProperty :: ClangBase m
=> String -- ^ A property name.
-> FFI.ClangString s' -- ^ A class USR.
-> ClangT s m (FFI.ClangString s)
createFromObjCProperty = FFI.constructUSR_ObjCProperty

0 comments on commit 4534208

Please sign in to comment.