এক্সেলে নিজেই তৈরি করুন 200 বছরের জন্য ডিজিটাল ক্যালেন্ডার -Make your own digital calendar for 200 years with Excel Vba

কিভাবে এক্সেলে 200 বছরের জন্য একটি ডিজিটাল ক্যালেন্ডার তৈরি করবেন?


এক্সেল ডিজিটাল ক্যালেন্ডার

মাইক্রোসফ্ট এক্সেল ফিল-ইন ক্যালেন্ডার সহ সময় সাশ্রয়ী ক্যালেন্ডার টেমপ্লেট তৈরী করুন যা আপনাকে সংগঠিত রাখতে অনুস্মারকগুলি এন্ট্রি করতে সক্ষম এবং মাসিক, সাপ্তাহিক বা দৈনিক এন্ট্রির জন্য ঘর অন্তর্ভুক্ত থাকে। 

এক্সেল ওয়ার্কশীটে  (ভিজ্যুয়াল বেসিক ফর অ্যাপ্লিকেশন VBA )  মাধ্যমে  কাস্টমাইজ করে ডিজিটাল ক্যালেন্ডার তৈরী করতে পারেন যাতে আপনার ফিউচার কোন তারিখে কোন দিন তা দেখার জন্য ক্যালেন্ডারের পাতায় খোঁজার প্রয়োজন নেই। উদাহরণস্বরূপ, আপনি এবং আপনার সহকর্মীরা আপনার সামনের দিনগুলির পরিকল্পনা করার সময় কোন তারিখে কোন দিন তা দেখার জন্য ডিজিটাল ক্যালেন্ডার খুব কম সময়ে দৃশ্যমান করে দিবে। 

চলুন শুরু করি ডিজিটাল ক্যালেন্ডার তৈরির কয়েকটি ধাপে: 

১:- ইন্সার্ট ইউজারফর্ম 
২:- cCalendar মডিউল  
৩:- Migration মডিউল
৪:- মডিউল

Migration মডিউল






ইউজারফর্ম  এবং মডিউলস এর জন্য কোডসexcel date userform

ইউজারফর্ম  এবং মডিউলস এর জন্য কোডস


ইউজারফর্ম এর জন্য কোডসexcel date userform


'For more : https://karimexcelvba.blogspot.com/
Private WithEvents Calendar1 As cCalendar
Dim i As Byte, sor, sor2, sor3 As String

Private Const GWL_STYLE As Long = -16
Private Const WS_SYSMENU As Long = &H80000

#If VBA7 Then
    Private Declare PtrSafe Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As LongPtr
    #If Win64 Then
        Private Declare PtrSafe Function GetWindowLong Lib "user32" Alias "GetWindowLongPtrA" (ByVal hWnd As LongPtr, ByVal nIndex As Long) As LongPtr
        Private Declare PtrSafe Function SetWindowLong Lib "user32" Alias "SetWindowLongPtrA" (ByVal hWnd As LongPtr, ByVal nIndex As Long, ByVal dwNewLong As LongPtr) As LongPtr
    #Else
        Private Declare PtrSafe Function GetWindowLong Lib "user32" Alias "GetWindowLongA" (ByVal hWnd As LongPtr, ByVal nIndex As Long) As LongPtr
        Private Declare PtrSafe Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hWnd As LongPtr, ByVal nIndex As Long, ByVal dwNewLong As LongPtr) As LongPtr
    #End If
#Else
    Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
    Private Declare Function GetWindowLong Lib "user32" Alias "GetWindowLongA" (ByVal hWnd As Long, ByVal nIndex As Long) As Long
    Private Declare Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hWnd As Long, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long
#End If

Public Sub RemoveCloseButton(frm As Object)
    #If VBA7 Then
        Dim lStyle As LongPtr, lFrmHandle As LongPtr
    #Else
        Dim lStyle As Long, lFrmHandle As Long
    #End If
    lFrmHandle = FindWindow("ThunderDFrame", frm.Caption)
    lStyle = GetWindowLong(lFrmHandle, GWL_STYLE)
    lStyle = lStyle And Not WS_SYSMENU
    SetWindowLong lFrmHandle, GWL_STYLE, lStyle
End Sub


Private Sub Calendar1_Click()
On Error Resume Next
Dim ara As Range
Set ara = Sheets("data").Range("A2:A" & Range("A" & Rows.Count).End(xlUp).Row).Find(CDate(Calendar1.Value), , xlValues, xlWhole)

If Not ara Is Nothing Then
Sheets("data").Cells(ara.Row, 1).Select
TextBox5.Text = Sheets("data").Cells(ara.Row, 2).Value
For i = 6 To 19
Controls("TextBox" & i).Text = Sheets("data").Cells(ara.Row, i - 3).Value
Next
Else
MsgBox "The selected date not available.", vbCritical, "Create by Karim Urmi "
End If
End Sub

Private Sub CommandButton1_Click()
Dim ara As Range, y As Byte
Set ara = Sheets("data").Range("A1:A" & Range("A" & Rows.Count).End(xlUp).Row).Find(CDate(Calendar1.Value), , xlValues, xlWhole)
If Not ara Is Nothing Then
Sheets("data").Cells(ara.Row, 2).Value = TextBox5.Text
For i = 6 To 18
Sheets("data").Cells(ara.Row, i - 3).Value = Controls("TextBox" & i).Text
Next
End If
sor2 = MsgBox("The data were saved", vbInformation, "Create by Karim Urmi")

For y = 2 To 16
Sheets("data").Columns(y).EntireColumn.WrapText = True
Next
End Sub
Private Sub CommandButton10_Click()
sor = MsgBox("Do you want to delete data?", vbYesNo, "Create by Karim Urmi")
If sor = vbNo Then Exit Sub
TextBox12.Value = ""
gir
End Sub
Private Sub CommandButton11_Click()
sor = MsgBox("Do you want to delete data?", vbYesNo, "Create by Karim Urmi")
If sor = vbNo Then Exit Sub
TextBox13.Value = ""
gir
End Sub

Private Sub CommandButton12_Click()
sor = MsgBox("Do you want to delete data?", vbYesNo, "Create by Karim Urmi")
If sor = vbNo Then Exit Sub
TextBox14.Value = ""
gir
End Sub

Private Sub CommandButton13_Click()
sor = MsgBox("Do you want to delete data?", vbYesNo, "Create by Karim Urmi")
If sor = vbNo Then Exit Sub
TextBox15.Value = ""
gir
End Sub

Private Sub CommandButton14_Click()
sor = MsgBox("Do you want to delete data?", vbYesNo, "Create by Karim Urmi")
If sor = vbNo Then Exit Sub
TextBox16.Value = ""
gir
End Sub

Private Sub CommandButton15_Click()
sor = MsgBox("Do you want to delete data?", vbYesNo, "Create by Karim Urmi")
If sor = vbNo Then Exit Sub

TextBox17.Value = ""
gir
End Sub

Private Sub CommandButton16_Click()
sor = MsgBox("Do you want to delete data?", vbYesNo, "Create by Karim Urmi")
If sor = vbNo Then Exit Sub
TextBox18.Value = ""
gir
End Sub

Private Sub CommandButton17_Click()
sor = MsgBox("Do you want to delete data?", vbYesNo, "Create by Karim Urmi")
If sor = vbNo Then Exit Sub
TextBox5.Value = ""
gir
End Sub

Private Sub CommandButton18_Click()
sor3 = MsgBox("Do you want to save the workbook?", vbYesNo, "Create by Karim Urmi")
If sor3 = vbNo Then
   ActiveWorkbook.Close SaveChanges:=False
   Else
   ActiveWorkbook.Save
   Application.Quit
   End If

End Sub

Private Sub CommandButton19_Click()
On Error Resume Next
Application.Goto Worksheets("Usr").Range("A1")
Unload Me
UserForm1.show

End Sub

Private Sub CommandButton3_Click()
Dim ara As Range
Set ara = Sheets("data").Range("A1:A" & Range("A" & Rows.Count).End(xlUp).Row).Find(CDate(Calendar1.Value), , xlValues, xlWhole)
If Not ara Is Nothing Then
Sheets("data").Cells(ara.Row, 2).Value = TextBox5.Text
For i = 6 To 18
Sheets("data").Cells(ara.Row, i - 3).Value = Controls("TextBox" & i).Text
Next
End If
sor2 = MsgBox("The data were changed", vbInformation, "Create by Karim Urmi")
End Sub

Private Sub CommandButton4_Click()
sor = MsgBox("Do you want to delete data?", vbYesNo, "Create by Karim Urmi")
If sor = vbNo Then Exit Sub
TextBox6.Value = ""
gir
End Sub

Private Sub Image1_Click()
TextBox6.Value = ""
CommandButton1.SetFocus
End Sub

Private Sub CommandButton5_Click()
sor = MsgBox("Do you want to delete data?", vbYesNo, "Create by Karim Urmi")
If sor = vbNo Then Exit Sub
TextBox7.Value = ""
gir
End Sub

Private Sub CommandButton6_Click()
sor = MsgBox("Do you want to delete data?", vbYesNo, "Create by Karim Urmi")
If sor = vbNo Then Exit Sub
TextBox8.Value = ""
gir
End Sub

Private Sub CommandButton7_Click()
sor = MsgBox("Do you want to delete data?", vbYesNo, "Create by Karim Urmi")
If sor = vbNo Then Exit Sub
TextBox9.Value = ""
gir
End Sub

Private Sub CommandButton8_Click()
sor = MsgBox("Do you want to delete data?", vbYesNo, "Create by Karim Urmi")
If sor = vbNo Then Exit Sub
TextBox10.Value = ""
gir
End Sub

Private Sub CommandButton9_Click()
sor = MsgBox("Do you want to delete data?", vbYesNo, "Create by Karim Urmi")
If sor = vbNo Then Exit Sub
TextBox11.Value = ""
gir
End Sub

Private Sub Kapat_Click()
Unload UserForm2
End Sub

Private Sub gir()
Dim ara As Range
Set ara = Sheets("data").Range("A1:A" & Range("A" & Rows.Count).End(xlUp).Row).Find(CDate(Calendar1.Value), , xlValues, xlWhole)
If Not ara Is Nothing Then
Sheets("data").Cells(ara.Row, 2).Value = TextBox5.Text
For i = 6 To 18
Sheets("data").Cells(ara.Row, i - 3).Value = Controls("TextBox" & i).Text
Next
End If
End Sub

Private Sub Frame1_Click()

End Sub

Private Sub UserForm_Initialize()
RemoveCloseButton Me
 
 Set Calendar1 = New cCalendar
    Calendar1.Add_Calendar_into_Frame Me.Frame1
TextBox6.EnterKeyBehavior = True
For i = 5 To 18
Controls("TextBox" & i).EnterKeyBehavior = True
Controls("TextBox" & i).ScrollBars = fmScrollBarsBoth
Next
Calendar1_Click

End Sub 
cCalendar মডিউল এর জন্য কোডসexcel date userform

Option Explicit

'#########################
'# Team authors:          #
'# Razaul Karim            #
'# Karim Urmi               #
'# Karim Excel VBA           #
'##############################

'# Event Triggered By Main Object
Public Event AfterUpdate()
Public Event BeforeUpdate(ByRef Cancel As Integer)
Public Event Click()
Public Event DblClick()

'# Members for Main Object
Private WithEvents CBxY As MSForms.ComboBox
Private WithEvents CBxM As MSForms.ComboBox

Private CLb As MSForms.Label
Private mDayButtons() As cCalendar
Private mLabelButtons() As cCalendar

Private PTitleNewFont As MSForms.NewFont
Private PDayNewFont As MSForms.NewFont
Private PGridNewFont As MSForms.NewFont
'# Members for Button Object
Private WithEvents CmB As MSForms.CommandButton
Private CmBl As MSForms.Label
Private CmBlNum As MSForms.Label
Private mcMain As cCalendar

'# For Properties
Private lPFontSize As Long
Private lPMonthLength As calMonthLength
Private lPDayLength As Long
Private bPYearFirst As Boolean
Private lPTitleFontColor As Long
Private lPGridFontColor As Long
Private lPDayFontColor As Long
Private lPFirstDay As calDayOfWeek
Private dValue As Date
Private lPBackColor As Long
Private lPMonth As Long
Private lPYear As Long
Private lPDay As Long
Private lPHeaderBackColor As Long
Private lPUseDefaultBackColors  As Boolean
Private bPVisible As Boolean
Private sPHeight As Single
Private sPWidth As Single
Private sPTop As Single
Private sPLeft As Single
Private lPSaturdayBackColor As Long
Private lPSundayBackColor As Long
Private sPControlTipText As String
Private bPTabStop As Boolean
Private lPTabIndex As Long
Private sPTag As String

Private bPShowDays As Boolean
Private bPShowTitle As Boolean
Private bPShowDateSelectors As Boolean
Private bPValueIsNull As Boolean

Private Const cDayFontColorSelected As Long = &H80000012
Private Const cDayFontColorInactive As Long = &H80000011
Private Const cBackColorInactive As Long = &H80000011
Private Const cDefaultWidth As Single = 216
Private Const cDefaultHeight As Single = 144

Public Enum calDayOfWeek
    dwMonday = 1
    dwTuesday = 2
    dwWednesday = 3
    dwThursday = 4
    dwFriday = 5
    dwSaturday = 6
    dwSunday = 7
End Enum

Public Enum calMonthLength
    mlLocalLong = 0
    mlLocalShort = 1
    mlENLong = 2
    mlENShort = 3
End Enum




'###########################
'# Properties for Main object
Private Sub AAA__Properties_Blank_for_compatibility()
End Sub

Public Property Get GridCellEffect() As Long
'Property Blank - not work
'Determines the effect used to display the grid.
End Property

Public Property Get GridLinesColor() As Long
'Property Blank - not work
'Determines the color used to display the lines in the grid.
End Property

Public Property Get ShowHorizontalGrid() As Boolean
'Property Blank - not work
'Specifies whether the calendar display horizontal gridlines.
End Property

Public Property Get ShowVerticalGrid() As Boolean
'Property Blank - not work
'Specifies whether to display vertical gridlines.
End Property

Public Property Get HelpContextID() As Long
'Property Blank - not work
'Specifies whether to display vertical gridlines.
End Property


'###########################
'# Properties for Main object
Private Sub AAA__Properties_Book()
End Sub

Public Property Get Tag() As String
    Tag = sPTag
End Property

Public Property Let Tag(sTag As String)
    sPTag = sTag
End Property

Public Property Get Parent() As Control
    If bInit Then
        Set Parent = CBxY.Parent.Parent
    Else
        Set Parent = Nothing
    End If
End Property

Public Property Get ValueIsNull() As Boolean
    ValueIsNull = bPValueIsNull
End Property

Public Property Let ValueIsNull(ByVal bValueIsNull As Boolean)
    bPValueIsNull = bValueIsNull
    If bInit Then
        Value = Value
    End If
End Property

Public Property Get ShowTitle() As Boolean
    ShowTitle = bPShowTitle
End Property

Public Property Let ShowTitle(ByVal bShowTitle As Boolean)
    bPShowTitle = bShowTitle
    If bInit Then
        CLb.Visible = bPShowTitle
        Move
    End If
End Property

Public Property Get ShowDays() As Boolean
    ShowDays = bPShowDays
End Property

Public Property Let ShowDays(ByVal bShowDays As Boolean)
    Dim i As Long
    bPShowDays = bShowDays
    If bInit Then
        For i = 0 To 6
            mLabelButtons(i).Obj_CmBl.Visible = bShowDays
        Next
        Move
    End If
End Property

Public Property Get ShowDateSelectors() As Boolean
    ShowDateSelectors = bPShowDateSelectors
End Property

Public Property Let ShowDateSelectors(ByVal bShowDateSelectors As Boolean)
    bPShowDateSelectors = bShowDateSelectors
    If bInit Then
        CBxY.Visible = bShowDateSelectors
        CBxM.Visible = bShowDateSelectors
        Move
    End If
End Property

Public Property Get TabIndex() As Long
    TabIndex = lPTabIndex
End Property

Public Property Let TabIndex(ByVal lTabIndex As Long)
    lPTabIndex = lTabIndex
    If bInit Then
        CBxY.Parent.TabIndex = lTabIndex
    End If
End Property

Public Property Get TabStop() As Boolean
    TabStop = bPTabStop
End Property

Public Property Let TabStop(ByVal bTabStop As Boolean)
    bPTabStop = bTabStop
    If bInit Then
        CBxY.Parent.TabStop = bTabStop
    End If
End Property

Public Property Get ControlTipText() As String
    ControlTipText = sPControlTipText
End Property

Public Property Let ControlTipText(ByVal sControlTipText As String)
    Dim i As Long
    sPControlTipText = sControlTipText
    If bInit Then
        For i = 0 To 6
            mLabelButtons(i).Obj_CmBl.ControlTipText = sControlTipText
        Next
        For i = 0 To 41
            mDayButtons(i).Obj_Cmb.ControlTipText = sControlTipText
        Next
        CBxM.ControlTipText = sControlTipText
        CBxY.ControlTipText = sControlTipText
        CLb.ControlTipText = sControlTipText
        'CBxY.Parent.ControlTipText = sControlTipText
    End If
End Property

Public Property Get GridFont() As MSForms.NewFont
    Set GridFont = PGridNewFont
End Property

Public Property Set GridFont(ByRef clGridNewFont As MSForms.NewFont)
    Set PGridNewFont = clGridNewFont
End Property

Public Property Get DayFont() As MSForms.NewFont
    Set DayFont = PDayNewFont
End Property

Public Property Set DayFont(ByRef clDayNewFont As MSForms.NewFont)
    Set PDayNewFont = clDayNewFont
End Property

Public Property Get TitleFont() As MSForms.NewFont
    Set TitleFont = PTitleNewFont
End Property

Public Property Set TitleFont(ByRef clTitleNewFont As MSForms.NewFont)
    Set PTitleNewFont = clTitleNewFont
End Property

Public Property Get Visible() As Boolean
    Visible = bPVisible
End Property

Public Property Let Visible(ByVal bVisible As Boolean)
    bPVisible = bVisible
    If bInit Then
        CBxY.Parent.Visible = bVisible
    End If
End Property

Public Property Get Left() As Single
    Left = sPLeft
End Property

Public Property Let Left(ByVal sLeft As Single)
    sPLeft = sLeft
    If bInit Then
        CBxY.Parent.Left = sLeft
    End If
End Property

Public Property Get Top() As Single
    Top = sPTop
End Property

Public Property Let Top(ByVal ssTop As Single)
    sPTop = ssTop
    If bInit Then
        CBxY.Parent.Top = ssTop
    End If
End Property

Public Property Get Height() As Single
    Height = sPHeight
End Property

Public Property Let Height(ByVal sHeight As Single)
    sPHeight = sHeight
    If bInit Then
        CBxY.Parent.Height = sHeight
        Move
    End If
End Property


Public Property Get Width() As Single
    Width = sPWidth
End Property

Public Property Let Width(ByVal sWidth As Single)
    'sWidth = Zero_Negative_Value(sWidth)
    sPWidth = sWidth
    If bInit Then
        CBxY.Parent.Width = sWidth
        Move
    End If
End Property

Public Property Get BackColor() As Long
    BackColor = lPBackColor
End Property

Public Property Let BackColor(ByVal lBackColor As Long)
    lPBackColor = lBackColor
    If bInit Then
        CBxY.Parent.BackColor = lBackColor
    End If
End Property

Public Property Get HeaderBackColor() As Long
    HeaderBackColor = lPHeaderBackColor
End Property

Public Property Let HeaderBackColor(ByVal lHeaderBackColor As Long)
Dim i As Long
    lPHeaderBackColor = lHeaderBackColor
    UseDefaultBackColors = False
End Property

Public Property Get UseDefaultBackColors() As Boolean
    UseDefaultBackColors = lPUseDefaultBackColors
End Property

Public Property Let UseDefaultBackColors(ByVal lUseDefaultBackColors As Boolean)
    lPUseDefaultBackColors = lUseDefaultBackColors
    If bInit Then
        Refresh
    End If
End Property

Public Property Get SaturdayBackColor() As Long
    SaturdayBackColor = lPSaturdayBackColor
End Property

Public Property Let SaturdayBackColor(ByVal lSaturdayBackColor As Long)
    lPSaturdayBackColor = lSaturdayBackColor
    UseDefaultBackColors = False
End Property

Public Property Get SundayBackColor() As Long
    SundayBackColor = lPSundayBackColor
End Property

Public Property Let SundayBackColor(ByVal lSundayBackColor As Long)
    lPSundayBackColor = lSundayBackColor
    'If bInit Then
    '    Refresh
    'End If
    UseDefaultBackColors = False

End Property

Public Property Get FirstDay() As calDayOfWeek
    FirstDay = lPFirstDay
End Property

Public Property Let FirstDay(ByVal vbFirstDay As calDayOfWeek)
    Dim i As Long, v
    
    Select Case vbFirstDay
        Case 1 To 7
        Case Else
            vbFirstDay = 1
    End Select
    
    lPFirstDay = vbFirstDay
    If bInit Then
        v = fWeekdayName(CInt(lPDayLength))
        For i = 0 To 6
            mLabelButtons(i).Obj_CmBl.Caption = v(((i + vbFirstDay - 1) Mod 7))
        Next
        Refresh
    End If
End Property

Public Property Get DayFontColor() As Long
    DayFontColor = lPDayFontColor
End Property

Public Property Let DayFontColor(ByVal lFontColor As Long)
    Dim i As Long
    
    lPDayFontColor = lFontColor
    If bInit Then
        For i = 0 To 6
            mLabelButtons(i).Obj_CmBl.ForeColor = lFontColor
        Next
    End If
End Property

Public Property Get GridFontColor() As Long
    GridFontColor = lPGridFontColor
End Property

Public Property Let GridFontColor(ByVal lFontColor As Long)
    Dim i As Long
    lPGridFontColor = lFontColor
    If bInit Then
        Refresh
    End If
End Property

Public Property Let TitleFontColor(ByVal lFontColor As Long)
    lPTitleFontColor = lFontColor
    If bInit Then
        CLb.ForeColor = lFontColor
    End If
End Property

Public Property Get TitleFontColor() As Long
    TitleFontColor = lPTitleFontColor
End Property

Public Property Get Month() As Long
    Month = lPMonth
End Property

Public Property Let Month(ByVal lMonth As Long)
    If lMonth = 0 Then
        Value = Empty
    Else
        If lMonth < 0 Then lMonth = lPMonth
        lMonth = fMin(lMonth, 12)
        Value = SumMonthsToDate(dValue, lMonth - lPMonth)
    End If
    lPMonth = lMonth
End Property

Public Property Get Year() As Long
    Year = lPYear
End Property

Public Property Let Year(ByVal lYear As Long)
    If lYear = 0 Then
        Value = Empty
    Else
        Value = VBA.DateSerial(CheckYear(lYear), VBA.Month(dValue), VBA.Day(dValue))
    End If
    lPYear = lYear
End Property

Public Property Get Day() As Long
    Day = lPDay
End Property

Public Property Let Day(ByVal lDay As Long)
    If lDay = 0 Then
        Value = Empty
    Else
        If lDay < 0 Then lDay = lPDay
        lDay = fMin(lDay, VBA.Day(VBA.DateSerial(VBA.Year(dValue), VBA.Month(dValue) + 1, 0)))
        Value = VBA.DateSerial(VBA.Year(dValue), VBA.Month(dValue), lDay)
    End If
    lPDay = lDay
End Property

Public Property Get Value() As Variant
    If bPValueIsNull Then
        Value = Empty
    Else
        Value = dValue
    End If
End Property

Public Property Let Value(ByVal newDate As Variant)
    Dim Cancel As Integer '*** Integer for backward compatibility
    
    If CheckValue(newDate) = False Then newDate = Empty

    RaiseEvent BeforeUpdate(Cancel)
    
    If Cancel = 0 Then 'Not canceled.

        If bInit And Not IsEmpty(newDate) Then
            CBxY.ListIndex = VBA.Year(newDate) - 1904
            CBxM.ListIndex = VBA.Month(newDate) - 1
        End If
        
        If (bPValueIsNull = IsEmpty(newDate)) Or (newDate <> dValue) Then
            If Not IsEmpty(newDate) Then
                dValue = newDate
            End If
            bPValueIsNull = IsEmpty(newDate)
            
            If bInit Then
                Refresh
            End If
        End If
        
        RaiseEvent AfterUpdate
    End If
End Property

Public Property Get DayLength() As calMonthLength
    DayLength = lPDayLength
End Property

Public Property Let DayLength(ByVal bDayLength As calMonthLength)
    Dim i As Long, v

    lPDayLength = bDayLength
    If bInit Then
        v = fWeekdayName(bDayLength)
        For i = 0 To 6
            mLabelButtons(i).Obj_CmBl.Caption = v(((i + lPFirstDay - 1) Mod 7))
        Next
    End If
End Property

Public Property Get MonthLength() As calMonthLength
    MonthLength = lPMonthLength
End Property

Public Property Let MonthLength(ByVal iMonthLength As calMonthLength)
    Dim i As Long, m

    lPMonthLength = iMonthLength

    If bInit Then
        CBxM.List = fMonthName(CLng(iMonthLength))
        Value = Value
    End If
End Property

Public Property Get YearFirst() As Boolean
    YearFirst = bPYearFirst
End Property

Public Property Let YearFirst(ByVal bYearFirst As Boolean)
    bPYearFirst = bYearFirst
    RenderLabel
End Property


'###########################
'# Properties for Day button objects
Private Sub AAA__Properties_for_Day_button_Book()
End Sub

Public Property Set Main(ByVal theMain As cCalendar)
    Set mcMain = theMain
End Property

Private Property Get Main() As cCalendar
    Set Main = mcMain
End Property

Public Property Get Obj_Cmb() As MSForms.CommandButton
    Set Obj_Cmb = CmB
End Property

Public Property Set Obj_Cmb(ByVal vNewValue As MSForms.CommandButton)
    Set CmB = vNewValue
End Property

Public Property Get Obj_CmBl() As MSForms.Label
    Set Obj_CmBl = CmBl
End Property

Public Property Set Obj_CmBl(ByVal vNewValue As MSForms.Label)
    Set CmBl = vNewValue
End Property

Public Property Set Obj_CmBlNum(ByVal vNewValue As MSForms.Label)
    Set CmBlNum = vNewValue
End Property

Public Property Get Obj_CmBlNum() As MSForms.Label
    Set Obj_CmBlNum = CmBlNum
End Property


'###########################
'# Public Methods
Private Sub AAA_Methods_Book()
End Sub

Public Sub AboutBox()
    MsgBox "Autori: r, Kris, Gabor"
End Sub

Public Sub Add( _
    ByVal fForm As MSForms.UserForm)

    Dim cFrame As MSForms.Frame
    Set cFrame = fForm.Controls.Add("Forms.Frame.1")
    
    With cFrame
        .Width = IIf(sPWidth < 0, cDefaultWidth, sPWidth)
        .Height = IIf(sPHeight < 0, cDefaultHeight, sPHeight)
    End With
    
    Add_Calendar_into_Frame cFrame
    
End Sub

Public Sub Add_Calendar_into_Frame(ByVal cFrame As MSForms.Frame)
    Dim i As Long
    Dim v(199)
    Dim w
    Dim dTemp As Date
    
    For i = 0 To 199
        v(i) = CStr(1904 + i)
    Next
    
    With cFrame
        .BackColor = BackColor
        .Caption = ""
        .SpecialEffect = 0
        '.Top = IIf(sPTop = -1, .Top, sPTop)
        '.Left = IIf(sPLeft = -1, .Left, sPLeft)
        '.Width = IIf(sPWidth < 0, .Width, sPWidth)
        '.Height = IIf(sPHeight < 0, .Height, sPHeight)
        .Visible = bPVisible
        'Top = .Top
        'Left = .Left
        'Width = .Width
        'Height = .Height
    End With
    
    
    'Add this first, for proper taborder (Need TabStop.)
    Set CLb = cFrame.Controls.Add("Forms.Label.1")
    Set CBxY = cFrame.Controls.Add("Forms.ComboBox.1")
    Set CBxM = cFrame.Controls.Add("Forms.ComboBox.1")
    
    ReDim mLabelButtons(6)
    ReDim mDayButtons(41)
    w = fWeekdayName(CInt(lPDayLength))
    
    For i = 0 To 6
        Set mLabelButtons(i) = New cCalendar
        Set mLabelButtons(i).Main = Me
        Set mLabelButtons(i).Obj_CmBl = cFrame.Controls.Add("Forms.Label.1")
        With mLabelButtons(i).Obj_CmBl
            .Caption = w(((i + lPFirstDay - 1) Mod 7))
            .ForeColor = DayFontColor
            .TextAlign = fmTextAlignCenter
            .BorderStyle = fmBorderStyleSingle
            .BorderColor = &H80000010 'Button shadow  &H80000015 'Button dark shadow
            '.SpecialEffect = fmSpecialEffectEtched
            If HeaderBackColor = -1 Then
                .BackColor = cBackColorInactive
                .BackStyle = fmBackStyleTransparent
            Else
                .BackColor = HeaderBackColor
                .BackStyle = fmBackStyleOpaque
            End If
        End With
    Next
            
    For i = 0 To 41
        Set mDayButtons(i) = New cCalendar
        Set mDayButtons(i).Main = Me
        
        Set mDayButtons(i).Obj_CmBl = cFrame.Controls.Add("Forms.Label.1")
        
        Set mDayButtons(i).Obj_CmBlNum = cFrame.Controls.Add("Forms.Label.1")
        With mDayButtons(i).Obj_CmBlNum
            .TextAlign = fmTextAlignCenter
            .BackStyle = fmBackStyleTransparent
        End With
        
        Set mDayButtons(i).Obj_Cmb = cFrame.Controls.Add("Forms.CommandButton.1")
        With mDayButtons(i).Obj_Cmb
            .BackStyle = fmBackStyleTransparent
        End With
    Next
    
    With CBxY
        .ListRows = 5
        .List = v
        .ListIndex = VBA.Year(dValue) - 1904
        .ShowDropButtonWhen = fmShowDropButtonWhenFocus
        .font.Bold = True
        .MatchRequired = True
    End With

    With CBxM
        .ListRows = 12
        .List = fMonthName(lPMonthLength)
        .ListIndex = VBA.Month(dValue) - 1
        .ShowDropButtonWhen = fmShowDropButtonWhenFocus
        .font.Bold = True
        .MatchRequired = True
    End With
    
    With CLb
        .ForeColor = TitleFontColor
        .TextAlign = fmTextAlignCenter
        .BackStyle = fmBackStyleTransparent
    End With
    
    ApplyFontChanges
    
    Refresh_Properities
    
    Move
    
End Sub

Private Sub ApplyFontChanges()
    Dim i As Long

    If Not PDayNewFont Is Nothing Then
        For i = 0 To 6
            With mLabelButtons(i).Obj_CmBl
                If .font.Bold <> DayFont.Bold Then _
                    .font.Bold = DayFont.Bold
                If .font.Weight <> DayFont.Weight Then _
                    .font.Weight = DayFont.Weight
                If .font.Charset <> DayFont.Charset Then _
                    .font.Charset = DayFont.Charset
                If .font.Italic <> DayFont.Italic Then _
                    .font.Italic = DayFont.Italic
                If .font.Name <> DayFont.Name Then _
                    .font.Name = DayFont.Name
                If .font.Size <> DayFont.Size Then _
                    .font.Size = DayFont.Size
                If DayFont.Strikethrough Then _
                    .font.Strikethrough = True
                If DayFont.Underline Then _
                    .font.Underline = True
            End With
        Next
    End If
            
    If Not PGridNewFont Is Nothing Then
        For i = 0 To 41
            With mDayButtons(i).Obj_CmBlNum
                If .font.Bold <> GridFont.Bold Then _
                    .font.Bold = GridFont.Bold
                If .font.Weight <> GridFont.Weight Then _
                    .font.Weight = GridFont.Weight
                If .font.Charset <> GridFont.Charset Then _
                    .font.Charset = GridFont.Charset
                If .font.Italic <> GridFont.Italic Then _
                    .font.Italic = GridFont.Italic
                If .font.Name <> GridFont.Name Then _
                    .font.Name = GridFont.Name
                If .font.Size <> GridFont.Size Then _
                    .font.Size = GridFont.Size
                If GridFont.Strikethrough Then _
                    .font.Strikethrough = True
                If GridFont.Underline Then _
                    .font.Underline = True
            End With
        Next
    End If
    
    If Not PTitleNewFont Is Nothing Then
        With CLb
                If .font.Bold <> TitleFont.Bold Then _
                    .font.Bold = TitleFont.Bold
                If .font.Weight <> TitleFont.Weight Then _
                    .font.Weight = TitleFont.Weight
                If .font.Charset <> TitleFont.Charset Then _
                    .font.Charset = TitleFont.Charset
                If .font.Italic <> TitleFont.Italic Then _
                    .font.Italic = TitleFont.Italic
                If .font.Name <> TitleFont.Name Then _
                    .font.Name = TitleFont.Name
                If .font.Size <> TitleFont.Size Then _
                    .font.Size = TitleFont.Size
                If TitleFont.Strikethrough Then _
                    .font.Strikethrough = True
                If TitleFont.Underline Then _
                    .font.Underline = True
        End With
    End If

End Sub

Public Sub Move( _
        Optional vLeft, _
        Optional vTop, _
        Optional vWidth, _
        Optional vHeight, _
        Optional vLayout)
        
    Dim i As Long, l As Currency, b As Currency, lc As Currency, bc As Currency
    Dim t As Long, b_ym As Currency, b_combo_m As Currency
    
    Const h_combo As Long = 16
    Const b_combo_y As Long = 42
    b_combo_m = IIf(lPMonthLength = mlENShort Or lPMonthLength = mlLocalShort, 42, 66) '66
    b_ym = b_combo_y + 2 + b_combo_m
    
    If bInit Then
        t = IIf(ShowDays, 7, 6)
        
        With CBxY.Parent 'Frame
            sPTop = IIf(IsMissing(vTop), IIf(Top = -1, .Top, Top), vTop)
            sPLeft = IIf(IsMissing(vLeft), IIf(Left = -1, .Left, Left), vLeft)
            sPHeight = IIf(IsMissing(vHeight), IIf(Height = -1, .Height, Height), vHeight)
            sPWidth = IIf(IsMissing(vWidth), IIf(Width = -1, .Width, Width), vWidth)
            
            l = Height
            b = Width
            l = Zero_Negative_Value(l - IIf(ShowTitle Or ShowDateSelectors, h_combo, 0) - 1)
            lc = CCur(l / t)
            bc = CCur(b / 7)
            b = bc * 7
            Debug.Print bc
            Debug.Print lc
            Debug.Print b
            Debug.Print l
            
        End With
        
        If ShowTitle Then
            With CLb
                .Width = Zero_Negative_Value(IIf(ShowDateSelectors, b - b_ym, b))
                .Height = h_combo
                .Left = 0
            End With
        End If
        
        If ShowDateSelectors Then
            With CBxY
                .Width = b_combo_y
                .Height = h_combo
                .Left = IIf(ShowTitle, CLb.Width, Int((b - b_ym) / 2)) + _
                       IIf(YearFirst, 0, b_combo_m + 2)
            End With
        
            With CBxM
                .Width = b_combo_m
                .Height = h_combo
                .Left = IIf(ShowTitle, CLb.Width, Int((b - b_ym) / 2)) + _
                       IIf(YearFirst, b_combo_y + 2, 0)
            End With
        End If
        If ShowDays Then
            For i = 0 To 6
                With mLabelButtons(i).Obj_CmBl
                    .Top = IIf(ShowTitle Or ShowDateSelectors, h_combo + 2, 0)
                    .Left = (i Mod 7) * bc - IIf(i > 0, 1, 0)
                    .Height = lc
                    .Width = bc + IIf(i > 0, 1, 0)
                End With
            Next
        End If
        For i = 0 To 41
            With mDayButtons(i).Obj_Cmb
                .Top = Int(i / 7) * lc + _
                       IIf(ShowTitle Or ShowDateSelectors, h_combo + 2, 0) + _
                       IIf(ShowDays, lc, 0)
                .Left = (i Mod 7) * bc
                .Height = lc
                .Width = bc
            End With
            With mDayButtons(i).Obj_CmBl
                .Top = mDayButtons(i).Obj_Cmb.Top
                .Left = mDayButtons(i).Obj_Cmb.Left
                .Height = mDayButtons(i).Obj_Cmb.Height
                .Width = mDayButtons(i).Obj_Cmb.Width
            End With
            
            With mDayButtons(i).Obj_CmBlNum
                .Top = Int(i / 7) * lc + _
                       IIf(ShowTitle Or ShowDateSelectors, h_combo, 0) + _
                       IIf(ShowDays, lc, 0) + 6
                .Left = (i Mod 7) * bc + 3
                .Height = Zero_Negative_Value(lc - 6)
                .Width = Zero_Negative_Value(bc - 6)
            End With

        Next
        
    Else
        sPHeight = IIf(IsMissing(Height), cDefaultHeight, Height)
        sPWidth = IIf(IsMissing(Width), cDefaultWidth, Width)
    End If
End Sub

Public Sub NextDay()
    Dim d As Date
    d = dValue + 1
    d = VBA.DateSerial(CheckYear(VBA.Year(d)), VBA.Month(d), VBA.Day(d))
    Value = d
End Sub

Public Sub NextWeek()
    Dim d As Date
    d = dValue + 7
    d = VBA.DateSerial(CheckYear(VBA.Year(d)), VBA.Month(d), VBA.Day(d))
    Value = d
End Sub

Public Sub NextMonth()
    Value = SumMonthsToDate(dValue, 1)
End Sub

Public Sub NextYear()
    Dim d As Date
    d = VBA.DateSerial(CheckYear(VBA.Year(dValue) + 1), VBA.Month(dValue), VBA.Day(dValue))
    Value = d
End Sub

Public Sub PreviousDay()
    Dim d As Date
    d = dValue - 1
    d = VBA.DateSerial(CheckYear(VBA.Year(d)), VBA.Month(d), VBA.Day(d))
    Value = d
End Sub

Public Sub PreviousWeek()
    Dim d As Date
    d = dValue - 7
    d = VBA.DateSerial(CheckYear(VBA.Year(d)), VBA.Month(d), VBA.Day(d))
    Value = d
End Sub

Public Sub PreviousMonth()
    Value = SumMonthsToDate(dValue, -1)
End Sub

Public Sub PreviousYear()
    Dim d As Date
    d = VBA.DateSerial(CheckYear(VBA.Year(dValue) - 1), VBA.Month(dValue), VBA.Day(dValue))
    Value = d
End Sub

Public Sub Today()
    Value = VBA.Date
End Sub

Public Sub Refresh()
    Refresh_Panel VBA.Month(dValue), VBA.Year(dValue)
    ApplyFontChanges
End Sub


'###########################
Private Sub AAA_Event_Book()
End Sub
'# Events for Main Object Components
'###########################

Private Sub CBxY_Change()
    RenderLabel
    Refresh_Panel CBxM.ListIndex + 1, CBxY.ListIndex + 1904
End Sub

Private Sub CBxM_Change()
    RenderLabel
    Refresh_Panel CBxM.ListIndex + 1, CBxY.ListIndex + 1904
End Sub

Private Sub CmB_Click()
    Main.Value = dValue
    Main.Event_click = True
End Sub

Private Sub CmB_DblClick(ByVal Cancel As MSForms.ReturnBoolean)
Main.Event_DblClick = True
End Sub


Private Sub CmB_KeyDown( _
    ByVal KeyCode As MSForms.ReturnInteger, _
    ByVal Shift As Integer)
    
    Dim newDate As Date

    '38 Up
    '37 Left
    '39 Right
    '40 Down
    
    newDate = dValue
    
    Select Case KeyCode
    Case 37
        newDate = newDate - 1
    Case 39
        newDate = newDate + 1
    Case 38
        newDate = newDate - 7
    Case 40
        newDate = newDate + 7
    Case 9
    End Select
    
    If newDate <> dValue Then
        Main.Value = newDate
        KeyCode = 0
    End If
End Sub


Private Sub Class_Initialize()
    bPShowDays = True
    bPShowTitle = True
    bPShowDateSelectors = True
    dValue = VBA.Date
    lPMonth = VBA.Month(VBA.Date)
    lPYear = VBA.Year(VBA.Date)
    lPDay = VBA.Day(VBA.Date)
    lPFontSize = 8
    lPMonthLength = 1
    lPDayLength = 1
    bPYearFirst = False
    lPTitleFontColor = &HA00000
    lPGridFontColor = &HA00000
    lPDayFontColor = &H0&
    lPFirstDay = 1
    lPBackColor = &H8000000F
    lPHeaderBackColor = 10053171 '&HFFAA99
    lPUseDefaultBackColors = True
    lPSaturdayBackColor = &H80000002
    lPSundayBackColor = &HFFAA99 '&H80000002
    bPVisible = True
    sPHeight = -1
    sPWidth = -1
    sPTop = -1
    sPLeft = -1
    sPControlTipText = ""
    
    Set TitleFont = New MSForms.NewFont
    With TitleFont
        .Name = "Arial"
        .Size = lPFontSize + 4
        .Bold = True
    End With
    
    Set DayFont = New MSForms.NewFont
    With DayFont
        .Name = "Arial"
        .Size = lPFontSize + 2
        .Bold = True
    End With
    
    Set GridFont = New MSForms.NewFont
    With GridFont
        .Name = "Arial"
        .Size = lPFontSize
    End With

End Sub

Private Sub Class_Terminate()
    Erase mDayButtons
    Erase mLabelButtons
    Set mcMain = Nothing
    Set PTitleNewFont = Nothing
    Set PDayNewFont = Nothing
    Set PGridNewFont = Nothing
    Set CBxY = Nothing
    Set CBxM = Nothing
    Set CmB = Nothing
    Set CLb = Nothing
    Set CmBl = Nothing
End Sub

'###########################
'# Private Function
Private Sub AAA_Private_Function_Book()
End Sub

Private Function ArraY_Days(ByVal lMonth As Long, ByVal lYear As Long)
    Dim v(41) As Date, i As Long, g As Long, l As Long, p As Long
    
    i = VBA.DateTime.Weekday( _
        VBA.DateSerial(lYear, lMonth, 1), 1 + lPFirstDay Mod 7) - 1
    
    
    If i = 0 Then i = 7
    
    g = VBA.Day(VBA.DateSerial(lYear, lMonth + 1, 0)) + i
    
    p = 1
    For l = i To 0 Step -1
        v(l) = VBA.DateSerial(lYear, lMonth, p)
        p = p - 1
    Next
    
    p = 0
    For l = i To g
        p = p + 1
        v(l) = VBA.DateSerial(lYear, lMonth, p)
    Next
    
    For l = g To 41
        v(l) = VBA.DateSerial(lYear, lMonth, p)
        p = p + 1
    Next
    ArraY_Days = v
End Function

Private Sub RenderLabel()
    Dim b As Currency, b_ym As Currency, b_combo_m As Long
    
    Const b_combo_y As Long = 42
    b_combo_m = IIf(lPMonthLength = mlENShort Or lPMonthLength = mlLocalShort, 42, 66) '66
    b_ym = b_combo_y + 2 + b_combo_m
    
    If bInit Then
        b = CBxY.Parent.Width
        If bPYearFirst Then
            CLb.Caption = CBxY.Value & " " & CBxM.Value
        Else
            CLb.Caption = CBxM.Value & " " & CBxY.Value
        End If
        CLb.Width = Zero_Negative_Value(IIf(ShowDateSelectors, b - b_ym, b))
        CBxM.Width = b_combo_m
        CBxY.Left = IIf(ShowTitle, CLb.Width, CCur((b - b_ym) / 2)) + _
                       IIf(YearFirst, 0, b_combo_m + 2)
        CBxM.Left = IIf(ShowTitle, CLb.Width, CCur((b - b_ym) / 2)) + _
                       IIf(YearFirst, b_combo_y + 2, 0)
        'CBxY.Left = IIf(ShowTitle, CLb.Width, IIf(CLb.Width, Int(CLb.Width / 2), 0)) + _
        '           IIf(YearFirst, 0, b_combo_m + 2)
        '
        'CBxM.Left = IIf(ShowTitle, CLb.Width, IIf(CLb.Width, Int(CLb.Width / 2), 0)) + _
        '           IIf(YearFirst, b_combo_y + 2, 0)
    End If
End Sub

Private Function bInit() As Boolean
    If Not CBxY Is Nothing Then bInit = True
End Function


Private Function SumMonthsToDate(dDate As Date, Optional lMonth As Long = 1) As Date
    Dim d As Date
    
    d = VBA.DateSerial( _
            VBA.Year(dDate), _
            VBA.Month(dDate) + lMonth, _
            fMin( _
                VBA.Day(dDate), _
                VBA.Day( _
                    VBA.DateSerial( _
                    VBA.Year(dDate), _
                    VBA.Month(dDate) + 1 + VBA.Abs(lMonth), _
                    0))))
                    
    If d = VBA.DateSerial(CheckYear(VBA.Year(d)), VBA.Month(d), VBA.Day(d)) Then
        SumMonthsToDate = d
    Else
        SumMonthsToDate = dDate
    End If
End Function

Private Function fMin(vFirstValue, ParamArray vValues())
    Dim i As Long
    fMin = vFirstValue
    
    If IsMissing(vValues) = False Then
    For i = 0 To UBound(vValues)
        If fMin > vValues(i) Then
            fMin = vValues(i)
        End If
    Next
    End If
End Function

Private Function fMonthName(lIndex As Long)
    Dim m(11), i As Long, v
    lIndex = lIndex Mod 4
    If Int(lIndex / 2) Then
        If lIndex Mod 2 Then
            v = Array("Jan", "Feb", "Mar", "Apr", "May", _
                "Jun", "Jul", "Aug", "Sep", "Oct", "Nov", "Dec")
        Else
            v = Array("January", "February", "March", _
                "April", "May", "June", "July", "August", _
                "September", "October", "November", "December")
        End If
        fMonthName = v
    Else
        For i = 0 To 11
            m(i) = VBA.Strings.MonthName(i + 1, lIndex Mod 2)
        Next
        fMonthName = m
    End If
End Function


Private Function fWeekdayName(lIndex As Long)
    Dim m(6), i As Long, v
    lIndex = lIndex Mod 4
    If Int(lIndex / 2) Then
        If lIndex Mod 2 Then
            v = Array("Mon", "Tue", "Wed", "Thu", "Fri", "Sat", "Sun")
        Else
            v = Array("Monday", "Tuesday", "Wednestay", _
                "Thursday", "Friday", "Saturday", "Sunday")
        End If
        fWeekdayName = v
    Else
        For i = 0 To 6
            m(i) = VBA.Strings.WeekdayName(i + 1, lIndex Mod 2, vbMonday)
        Next
        fWeekdayName = m
    End If
End Function


Private Function CheckYear(ByVal lYear As Long) As Long
    Select Case lYear
    Case Is < 1904
        CheckYear = 1904
    Case 1904 To 2103
        CheckYear = lYear
    Case Else
        CheckYear = 2103
    End Select
End Function

'###########################
'# Private Sub
Private Sub AAA_Private_Sub_Book()
End Sub

Public Property Let Event_DblClick(ByVal x As Boolean)
    RaiseEvent DblClick
End Property

Private Property Get Event_DblClick() As Boolean
    Event_DblClick = False
End Property


Public Property Let Event_click(ByVal x As Boolean)
    RaiseEvent Click
End Property

Private Property Get Event_click() As Boolean
    Event_click = False
End Property

Private Sub Refresh_Properities()
    With Me
        .BackColor = .BackColor
        .ControlTipText = .ControlTipText
        .DayFontColor = .DayFontColor
        .DayLength = .DayLength
        .GridFontColor = .GridFontColor
        .MonthLength = .MonthLength
        If .UseDefaultBackColors = False Then
            .SaturdayBackColor = .SaturdayBackColor
            .SundayBackColor = .SundayBackColor
            .HeaderBackColor = .HeaderBackColor
        End If
        .ShowDateSelectors = .ShowDateSelectors
        .ShowDays = .ShowDays
        .ShowTitle = .ShowTitle
        .TabIndex = .TabIndex
        .TabStop = .TabStop
        .TitleFontColor = .TitleFontColor
        .ValueIsNull = .ValueIsNull
        .YearFirst = .YearFirst
    End With
End Sub

Private Sub Refresh_Selected_Day(ByVal dValue As Date)
    Dim i As Long, c As MSForms.Label
    For i = 0 To 41
        If mDayButtons(i).Value = dValue And Not bPValueIsNull Then
            On Error Resume Next
            mDayButtons(i).Obj_Cmb.SetFocus
            On Error GoTo 0
            With mDayButtons(i).Obj_CmBl
                .BackStyle = fmBackStyleOpaque
                .BackColor = cBackColorInactive
                .ForeColor = cDayFontColorSelected
            End With
            lPMonth = VBA.Month(dValue)
            lPYear = VBA.Year(dValue)
            lPDay = VBA.Day(dValue)
        End If
    Next

End Sub

Private Sub Refresh_Panel(ByVal lMonth As Long, ByVal lYear As Long)
    Dim v, i As Long, l As Long
    Dim iDay As Long
    
    If bInit Then
        v = ArraY_Days(lMonth, lYear)
        For i = 0 To 41
            mDayButtons(i).Value = v(i)
            With mDayButtons(i).Obj_CmBlNum
                If .Caption <> VBA.Day(v(i)) Then
                    .Caption = VBA.Day(v(i))
                End If
                If lMonth = VBA.Month(v(i)) Then
                    If .ForeColor <> GridFontColor Then
                        .ForeColor = GridFontColor
                    End If
                Else
                    If .ForeColor <> cDayFontColorInactive Then
                        .ForeColor = cDayFontColorInactive
                    End If
                End If
            End With
            With mDayButtons(i).Obj_CmBl
                If .BackStyle = fmBackStyleOpaque Then
                    .BackStyle = fmBackStyleTransparent
                End If
                If UseDefaultBackColors = False Then
                    iDay = VBA.DateTime.Weekday(v(i))
                    If iDay = vbSaturday Then
                        If .BackColor <> lPSaturdayBackColor Then
                            .BackColor = lPSaturdayBackColor
                        End If
                        If .BackStyle <> fmBackStyleOpaque Then
                            .BackStyle = fmBackStyleOpaque
                        End If
                    ElseIf iDay = vbSunday Then
                        If .BackColor <> lPSundayBackColor Then
                            .BackColor = lPSundayBackColor
                        End If
                        If .BackStyle <> fmBackStyleOpaque Then
                            .BackStyle = fmBackStyleOpaque
                        End If
                    End If
                End If
            End With
            If CheckValue(v(i)) = False Then
                mDayButtons(i).Obj_Cmb.Locked = True
            Else
                If mDayButtons(i).Obj_Cmb.Locked = True Then
                    mDayButtons(i).Obj_Cmb.Locked = False
                End If
            End If
        Next
        
        If UseDefaultBackColors = False Then
            For l = 0 To 6
                If mLabelButtons(l).Obj_CmBl.BackStyle = fmBackStyleTransparent Then _
                    mLabelButtons(l).Obj_CmBl.BackStyle = fmBackStyleOpaque
                If mLabelButtons(l).Obj_CmBl.BackColor <> lPHeaderBackColor Then _
                    mLabelButtons(l).Obj_CmBl.BackColor = lPHeaderBackColor
            Next
        Else
            For l = 0 To 6
                If mLabelButtons(l).Obj_CmBl.BackStyle = fmBackStyleOpaque Then _
                    mLabelButtons(l).Obj_CmBl.BackStyle = fmBackStyleTransparent
            Next
        End If
        
        If lMonth = VBA.Month(dValue) And lYear = VBA.Year(dValue) Then
            Refresh_Selected_Day dValue
        Else
            lPMonth = 0
            lPYear = 0
            lPDay = 0
        End If
    End If
End Sub

Private Function CheckValue(d) As Boolean
If VarType(d) = vbDate Then
    Select Case d
        Case 1462 To 74510
            CheckValue = CLng(d) = d
    End Select
End If
End Function

Private Function Zero_Negative_Value(sNumber As Single) As Single
If sNumber > 0 Then
    Zero_Negative_Value = sNumber
End If
End Function 
Migration মডিউল এর জন্য কোডসexcel date userform

Option Explicit


Function Migration_of_Calendar_Classes(fUserForm As Object) As String
    Dim s As String
    Dim oc As Object
    Dim c As Object 'MSACAL.Calendar
    
    For Each oc In fUserForm.Controls
        If TypeName(oc) = "Calendar" Then
            s = s & "Private WithEvents " & oc.Name & " As cCalendar" & vbNewLine & vbNewLine
        End If
    Next
    
    If Len(s) = 0 Then
        Exit Function
    End If
    
    s = "'Copy these declarations to the source code window of your userform: " & fUserForm.Name & vbNewLine & s
    s = s & vbNewLine
    s = s & vbNewLine
    s = s & "'" & String(100, "#") & vbNewLine
    s = s & vbNewLine
    s = s & "'Subroutine for setting up the new calendar object(s)." & vbNewLine
    s = s & "'The below subroutine should be called from the " & vbNewLine
    s = s & "'UserForm_Initialize() event handler of your userform: " & fUserForm.Name & vbNewLine
    s = s & vbNewLine
    s = s & "Private Sub Setup_Calendar_Classes_for_" & fUserForm.Name & "()" & vbNewLine
    
    For Each oc In fUserForm.Controls
        If TypeName(oc) = "Calendar" Then
    
            Set c = oc
            
            s = s & vbNewLine
            s = s & "    'Setting Object Class:" & vbNewLine
            s = s & "    Set " & c.Name & " = New cCalendar" & vbNewLine
            s = s & vbNewLine
            s = s & "    'Changed Property Values:" & vbNewLine
            
                     
            s = s & "    With " & c.Name & vbNewLine
    
            If c.BackColor <> &H8000000F Then _
                s = s & "        .BackColor = " & c.BackColor & vbNewLine
    
            If c.ControlTipText <> "" Then _
                s = s & "        .ControlTipText = """ & c.ControlTipText & """" & vbNewLine
    
            If c.DayFont.Name <> "Arial" Then _
                s = s & "        .DayFont.Name = """ & c.DayFont.Name & """" & vbNewLine
    
            If c.DayFont.Size <> 9 Then _
                s = s & "        .DayFont.Size = " & c.DayFont.Size & vbNewLine
    
            If c.DayFont.Bold = False Then _
                s = s & "        .DayFont.Bold = False" & vbNewLine
    
            If c.DayFont.Italic = True Then _
                s = s & "        .DayFont.Italic = True" & vbNewLine
    
            If c.DayFont.Strikethrough = True Then _
                s = s & "        .DayFont.Strikethrough = True " & vbNewLine
    
            If c.DayFont.Underline = True Then _
                s = s & "        .DayFont.Underline = True " & vbNewLine
    
            If c.DayFontColor <> 0 Then _
                s = s & "        .DayFontColor = " & c.DayFontColor & vbNewLine
    
            If c.DayLength <> 1 Then _
                s = s & "        .DayLength = " & c.DayLength & vbNewLine
    
            If c.FirstDay <> 1 Then _
                s = s & "        .FirstDay = " & c.FirstDay & vbNewLine
    
            If c.GridFont.Name <> "Arial" Then _
                s = s & "        .GridFont.Name = """ & c.GridFont.Name & """" & vbNewLine
    
            If c.GridFont.Size <> 8 Then _
                s = s & "        .GridFont.Size = " & c.GridFont.Size & vbNewLine
    
            If c.GridFont.Bold = False Then _
                s = s & "        .GridFont.Bold = False" & vbNewLine
    
            If c.GridFont.Italic = True Then _
                s = s & "        .GridFont.Italic = True" & vbNewLine
    
            If c.GridFont.Strikethrough = True Then _
                s = s & "        .GridFont.Strikethrough = True " & vbNewLine
    
            If c.GridFont.Underline = True Then _
                s = s & "        .GridFont.Underline = = True " & vbNewLine
    
            If c.GridFontColor <> &HA00000 Then _
                s = s & "        .GridFontColor = " & c.GridFontColor & vbNewLine
    
            If c.MonthLength <> 1 Then _
                s = s & "        .MonthLength = " & c.MonthLength & vbNewLine
    
            If c.ShowDateSelectors = False Then _
                s = s & "        .ShowDateSelectors = False" & vbNewLine
    
            If c.ShowDays = False Then _
                s = s & "        .ShowDays = False" & vbNewLine
    
            If c.ShowTitle = False Then _
                s = s & "        .ShowTitle = False" & vbNewLine
    
            If c.ShowHorizontalGrid = False Then _
                s = s & "        .ShowHorizontalGrid = Not Compatible" & vbNewLine
    
            If c.TabStop = False Then _
                s = s & "        .TabStop = False" & vbNewLine
    
            If c.Tag <> "" Then _
                s = s & "        .Tag = """ & c.Tag & """" & vbNewLine
    
            If c.TitleFont.Name <> "Arial" Then _
                s = s & "        .TitleFont.Name = """ & c.TitleFont.Name & """" & vbNewLine
    
            If c.TitleFont.Size <> 8 Then _
                s = s & "        .TitleFont.Size = " & c.TitleFont.Size & vbNewLine
    
            If c.TitleFont.Bold = False Then _
                s = s & "        .TitleFont.Bold = False" & vbNewLine
    
            If c.TitleFont.Italic = True Then _
                s = s & "        .TitleFont.Italic = True" & vbNewLine
    
            If c.TitleFont.Strikethrough = True Then _
                s = s & "        .TitleFont.Strikethrough = True " & vbNewLine
    
            If c.TitleFont.Underline = True Then _
                s = s & "        .TitleFont.Underline = = True " & vbNewLine
    
            If c.TitleFontColor <> 10485760 Then _
                s = s & "        .TitleFontColor = " & c.TitleFontColor & vbNewLine
    
            If c.ValueIsNull = True Then _
                s = s & "        .ValueIsNull = True" & vbNewLine
    
            If c.Visible = False Then _
                s = s & "        .Visible = False" & vbNewLine
    
            s = s & "    'Code for putting your calendar into an existing frame:" & vbNewLine
            s = s & "    '    .Add_Calendar_into_Frame " & fUserForm.Name & ".<write here the name of your frame>" & vbNewLine
            s = s & vbNewLine
            s = s & "    'Code for creating the new Calendar item on form " & fUserForm.Name & vbNewLine
            s = s & "    'Position Property Values:" & vbNewLine
            s = s & "        .Left = " & c.Left & vbNewLine
            s = s & "        .Top = " & c.Top & vbNewLine
            s = s & "        .Height = " & c.Height & vbNewLine
            s = s & "        .Width = " & c.Width & vbNewLine
            s = s & "    'Adding to the form:" & vbNewLine
            s = s & "        .Add " & fUserForm.Name & vbNewLine
            s = s & "    End With " & vbNewLine
        End If
    Next
    
    s = s & "End Sub"
    
    Migration_of_Calendar_Classes = s
End Function


 
 Module1মডিউল ১ এর জন্য কোডসexcel date userform
Sub Auto_Open()
UserForm2.show
Application.Visible = True
End Sub

Sub boya()
Dim rw As Variant
Dim Rng As Range

Set Rng = Sheets("data").Range("A2:A2193") 'Change this range to whatever you want

For Each rw In Rng.Rows 'For each row in your range...
    If rw.Row Mod 2 = 0 Then 'check to see if the row is even
        rw.Interior.ColorIndex = 36 'if the row is even, insert a blank row above it
    Else
    rw.Interior.ColorIndex = 19
    End If
Next rw 'Keep going until you are out of rows

End Sub

Sub merkez()
    Dim i&, a&, s&, t&
    If TypeName(Selection) <> "Range" Then Exit Sub
    If Rows(Rows.Count).EntireRow.Hidden Or Columns(Columns.Count).EntireColumn.Hidden Then
        Cells.EntireColumn.Hidden = False
        Cells.EntireRow.Hidden = False
        Exit Sub
    End If
    i = Selection.Rows(1).Row
    a = i + Selection.Rows.Count - 1
    s = Selection.Columns(1).Column
    t = s + Selection.Columns.Count - 1
    Application.ScreenUpdating = False
    On Error Resume Next
    Range(Cells(1, 1), Cells(i - 1, 1)).EntireRow.Hidden = True
    Range(Cells(a + 1, 1), Cells(Rows.Count, 1)).EntireRow.Hidden = True

    Range(Cells(1, 1), Cells(1, s - 1)).EntireColumn.Hidden = True
    Range(Cells(1, t + 1), Cells(1, Columns.Count)).EntireColumn.Hidden = True
    Application.ScreenUpdating = True
End Sub


একটি মন্তব্য পোস্ট করুন

0 মন্তব্যসমূহ