Skip to content

Commit

Permalink
Signed-off-by: unknown <EMFYON@LBNL07489.corp.capgemini.com>
Browse files Browse the repository at this point in the history
  • Loading branch information
unknown authored and unknown committed Jul 11, 2012
1 parent 04dfd5e commit 29488ee
Show file tree
Hide file tree
Showing 3 changed files with 351 additions and 0 deletions.
127 changes: 127 additions & 0 deletions Files.bas
@@ -0,0 +1,127 @@
Attribute VB_Name = "Files"


'---------------------------------------------------------------------------------------------------------------------------------------------
'
' File Library v0.1
'
'
' Functions lists
' ---------------
'
' + Function writeFile (ByVal file As String, ByVal content As String) As String : overwrite the content specified in the file specified.
' * Specifications / limitations
' - If the file does not exists, the file is created
' - The folder has to exist
' * Arguments
' - file as String : the full path of the file
' - content as String : the content that has to be written into the file
'
' + Function readFile(ByVal file As String) As String : read the content of a file and return a single line with all the content
' * Specifications / limitations
' - The file has to Exists, no error handling
' - The content is retrieved without any line returns (line returns are replaced by space)
' * Arguments
' - file as String : the full path of the file
' + Function readFileAndTruncate(ByVal file As String) As String : calls readFile() and then truncate the text to 30000 characters in order to avoid Excel limitations
' * Specifications / limitations
' - The file has to Exists, no error handling
' - The content is retrieved without any line returns (line returns are replaced by space)
' - Only the 30.000 first characters are retrieved
' * Arguments
' - file as String : the full path of the file
'
' Revisions history
' -----------------
' - Emile Fyon 11/07/2012 v0.1 Creation
'
'---------------------------------------------------------------------------------------------------------------------------------------------






'---------------------------------------------------------------------------------------------------------------------------------------------
' + writeFile (ByVal file As String, ByVal content As String) : overwrite the content specified in the file specified.
' * Specifications / limitations
' - If the file does not exists, the file is created
' - The folder has to exist
' * Arguments
' - file as String : the full path of the file
' - content as String : the content that has to be written into the file
'
' Last edition date : 11/07/2012
'
' Revisions history
' -----------------
' - Emile Fyon 11/07/2012 Creation
'
'---------------------------------------------------------------------------------------------------------------------------------------------

Function writeFile(ByVal file As String, ByVal content As String) As String

Open file For Output As #1
Print #1, content
Close #1

writeFile = "File updated yet"

End Function

'---------------------------------------------------------------------------------------------------------------------------------------------
' + readFile(ByVal file As String) As String : read the content of a file and return a single line with all the content
' * Specifications / limitations
' - The file has to Exists, no error handling
' - The content is retrieved without any line returns (line returns are replaced by space)
' * Arguments
' - file as String : the full path of the file
'
'
' Last edition date : 11/07/2012
'
' Revisions history
' -----------------
' - Emile Fyon 11/07/2012 Creation
'
'---------------------------------------------------------------------------------------------------------------------------------------------

Function readFile(ByVal file As String) As String

Dim MyString, MyNumber
Open file For Input As #1 ' Open file for input.
fileContent = ""
Do While Not EOF(1) ' Loop until end of file.
Line Input #1, MyString
Debug.Print MyString
fileContent = fileContent & MyString & " "
Loop
Close #1 ' Close file.
readFile = fileContent
End Function


'---------------------------------------------------------------------------------------------------------------------------------------------
' + readFileAndTruncate(ByVal file As String) As String : calls readFile() and then truncate the text to 30000 characters in order to avoid Excel limitations
' * Specifications / limitations
' - The file has to Exists, no error handling
' - The content is retrieved without any line returns (line returns are replaced by space)
' - Only the 30.000 first characters are retrieved
' * Arguments
' - file as String : the full path of the file
'
'
' Last edition date : 11/07/2012
'
' Revisions history
' -----------------
' - Emile Fyon 11/07/2012 Creation
'
'---------------------------------------------------------------------------------------------------------------------------------------------


Function readFileAndTruncate(ByVal file As String) As String

readFileAndTruncate = Left(readFile(file), 30000)

End Function
81 changes: 81 additions & 0 deletions RangeActions.bas
@@ -0,0 +1,81 @@
Attribute VB_Name = "RangeActions"


'---------------------------------------------------------------------------------------------------------------------------------------------
'
' Range Actions Library v0.1
'
'
' Functions lists
' ---------------
'
' + Sub addLinks () : add an hyperlink to all the cells in the current selection. The URL will be the content of the cell
' * Specifications / limitations
' - None
' * Arguments
' - None
' + Sub addLink (ByVal url As String, ByVal cell As Range) : add an hyperlink to cell given in argument to the URL given in argument. The URL will be the content of the cell
' * Specifications / limitations
' - None
' * Arguments
' - ByVal url As String the URL the cell must point to
' - ByVal cell As Range the cell to add the link
'
' Revisions history
' -----------------
' - Emile Fyon 11/07/2012 v0.1 Creation
'
'---------------------------------------------------------------------------------------------------------------------------------------------






'---------------------------------------------------------------------------------------------------------------------------------------------
' + Sub addLinks () : add an hyperlink to all the cells in the current selection. The URL will be the content of the cell
' * Specifications / limitations
' - None
' * Arguments
' - None
'
' Last edition date : 11/07/2012
'
' Revisions history
' -----------------
' - Emile Fyon 11/07/2012 Creation
'
'---------------------------------------------------------------------------------------------------------------------------------------------

Sub addLinks()

For Each cell In Selection
Call addLink(cell.Value, cell)
Next

End Sub

'---------------------------------------------------------------------------------------------------------------------------------------------
' + Sub addLink (ByVal url As String, ByVal cell As Range) : add an hyperlink to cell given in argument to the URL given in argument. The URL will be the content of the cell
' * Specifications / limitations
' - None
' * Arguments
' - ByVal url As String the URL the cell must point to
' - ByVal cell As Range the cell to add the link
'
' Last edition date : 11/07/2012
'
' Revisions history
' -----------------
' - Emile Fyon 11/07/2012 Creation
'
'---------------------------------------------------------------------------------------------------------------------------------------------

Sub addLink(ByVal url As String, ByVal cell As Range)

cell.Worksheet.Hyperlinks.Add Anchor:=cell, Address:=url


End Sub


143 changes: 143 additions & 0 deletions Regex.bas
@@ -0,0 +1,143 @@
Attribute VB_Name = "Regex"
'---------------------------------------------------------------------------------------------------------------------------------------------
'
' Regex Library v0.1
'
'
' Functions lists
' ---------------
'
' + Function matchExpreg(ByVal txt As String, ByVal matchPattern As String, ByVal replacePattern As String) As String
' * Description : Match the specified pattern in the text given in argument and apply the replacementPattern
' * Specifications / limitations
' - Multiline
' - Not case sensitive
' * Arguments
' - ByVal txt As String : the text to search in
' - ByVal matchPattern As String : the regular expression pattern
' - ByVal replacePattern As String : the replacement pattern
' + Function findExpreg(ByVal cellContent As Range, ByVal cellPattern As Range) As String
' * Description : Return the first occurence of the regular expression pattern found in the given expression
' * Specifications / limitations
' - Multiline
' - Not case sensitive
' * Arguments
' - ByVal txt As String : the text to search in
' - ByVal matchPattern As String : the regular expression pattern
' + Function stripTags(ByVal txt As String) As String
' * Description : Strips all the tags within a given string
' * Specifications / limitations
' - None
' * Arguments
' - ByVal txt As String : the text to search in'
'
'
' Revisions history
' -----------------
' - Emile Fyon 11/07/2012 v0.1 Creation
'
'---------------------------------------------------------------------------------------------------------------------------------------------




'---------------------------------------------------------------------------------------------------------------------------------------------
' + Function matchExpreg(ByVal txt As String, ByVal matchPattern As String, ByVal replacePattern As String) As String
' * Description : Match the specified pattern in the text given in argument and apply the replacementPattern
' * Specifications / limitations
' - Multiline
' - Not case sensitive
' * Arguments
' - ByVal txt As String : the text to search in
' - ByVal matchPattern As String : the regular expression pattern
' - ByVal replacePattern As String : the replacement pattern
'
'
' Last edition date : 11/07/2012
'
' Revisions history
' -----------------
' - Emile Fyon 11/07/2012 Creation
'
'---------------------------------------------------------------------------------------------------------------------------------------------


Function matchExpreg(ByVal txt As String, ByVal matchPattern As String, ByVal replacePattern As String) As String
Dim RE As Object, REMatches As Object

' Set cell = Range("e15")
' strData = cell.Value

Dim reg_exp As New RegExp
reg_exp.Pattern = matchPattern
reg_exp.IgnoreCase = True
reg_exp.Global = True

txt = reg_exp.Replace(txt, replacePattern)
matchExpreg = txt


End Function


'---------------------------------------------------------------------------------------------------------------------------------------------
' + Function findExpreg(ByVal cellContent As Range, ByVal cellPattern As Range) As String
' * Description : Return the first occurence of the regular expression pattern found in the given expression
' * Specifications / limitations
' - Multiline
' - Not case sensitive
' * Arguments
' - ByVal txt As String : the text to search in
' - ByVal matchPattern As String : the regular expression pattern
'
'
' Last edition date : 11/07/2012
'
' Revisions history
' -----------------
' - Emile Fyon 11/07/2012 Creation
'
'---------------------------------------------------------------------------------------------------------------------------------------------


Function findExpreg(ByVal txt As String, ByVal matchPattern As String) As String


Dim expReg As New RegExp
expReg.Pattern = matchPattern
expReg.IgnoreCase = True
expReg.Global = True

Set res = expReg.Execute(txt)

txt = res(0).submatches(0)
findExpreg = txt


End Function

'---------------------------------------------------------------------------------------------------------------------------------------------
' + Function stripTags(ByVal txt As String) As String
' * Description : Strips all the tags within a given string
' * Specifications / limitations
' - None
' * Arguments
' - ByVal txt As String : the text to search in
'
'
' Last edition date : 11/07/2012
'
' Revisions history
' -----------------
' - Emile Fyon 11/07/2012 Creation
'
'---------------------------------------------------------------------------------------------------------------------------------------------


Function stripTags(ByVal txt As String) As String

regMask = "(<.+?>)"
stripTags = matchExpreg(txt, regMask, "")


End Function

0 comments on commit 29488ee

Please sign in to comment.