概要
以下は 「UI 自動生成ツール(コード自動注入版)」 の完全なテンプレートです。
このツールはボタン一発で UserForm を作成 → 必要なコントロールを配置 → 動作用コードをフォームのコードモジュールに自動注入 します。
実務でそのまま使えるよう、カレンダー・日付範囲・プログレス・検索・ログイン・一覧→詳細・行編集・ドロップダウン一覧・高機能検索 の各 UI をサポートします。
注意事項(事前準備・制限)
- [ツール → マクロの設定]で「VBA プロジェクト オブジェクト モデルへのアクセスを信頼する」を有効にしてください。
- 生成処理は
ThisWorkbook.VBProjectを使います(信頼設定が必要)。 - 生成された UserForm はすぐ編集できます(名前・位置・スタイルの微調整はIDEで)。
配布ファイル構成(想定)
- Module:
modUIBuilderInject(下記コードを丸ごと貼る) - (任意)メインフォーム:
frmUI_Generator(GUIで選択実行したい場合。下に簡易コード例あり)
全コード(Module: modUIBuilderInject)
下記をそのまま標準モジュールに貼ってください。必要に応じてコメントを参照して調整できます。
Option Explicit
' Module: modUIBuilderInject
' Purpose: Create UserForms with controls and inject functional code automatically.
' ---------- Utility: Create new UserForm ----------
Function CreateNewForm(formName As String) As VBComponent
' Returns VBComponent of newly created UserForm
Dim vbComp As VBComponent
On Error Resume Next
'もし同名があれば先に削除(安全のため)
ThisWorkbook.VBProject.VBComponents.Remove ThisWorkbook.VBProject.VBComponents(formName)
On Error GoTo 0
Set vbComp = ThisWorkbook.VBProject.VBComponents.Add(vbext_ct_MSForm)
vbComp.Name = formName
Set CreateNewForm = vbComp
End Function
' ---------- Utility: Add a control to a form (Designer Controls) ----------
Sub AddControlToForm(frmComp As VBComponent, ctrlProgID As String, ctrlName As String, _
left As Single, top As Single, width As Single, height As Single, Optional caption As String = "")
' ctrlProgID example: "Forms.Label.1", "Forms.TextBox.1", "Forms.CommandButton.1", "Forms.ListBox.1", "Forms.ComboBox.1", "Forms.OptionButton.1"
Dim c As MSForms.Control
Set c = frmComp.Designer.Controls.Add(ctrlProgID, ctrlName, True)
c.Left = left
c.Top = top
c.Width = width
c.Height = height
On Error Resume Next
If caption <> "" Then
'ラベル類は Caption、TextBoxは Text、ListBox/ComboBox は何もしない
c.Caption = caption
c.Text = caption
End If
On Error GoTo 0
End Sub
' ---------- Utility: Inject code into the form's code module ----------
Sub InjectFormCode(frmComp As VBComponent, code As String)
With frmComp.CodeModule
.InsertLines .CountOfLines + 1, code
End With
End Sub
' ---------- Helper: Simple message to confirm creation ----------
Sub Confirm(msg As String)
MsgBox msg, vbInformation
End Sub
' ---------- Main: Build UI with injected functionality ----------
Sub BuildUI_WithCode(uiType As String)
Dim name As String
Dim frm As VBComponent
name = "UI_" & Replace(Format(Now, "yyyymmdd_hhnnss"), ":", "")
Set frm = CreateNewForm(name)
Select Case uiType
Case "カレンダー入力"
Build_Calendar_WithCode frm
Case "日付範囲ピッカー"
Build_DateRange_WithCode frm
Case "プログレスバー"
Build_Progress_WithCode frm
Case "検索ダイアログ"
Build_Search_WithCode frm
Case "ログイン画面"
Build_Login_WithCode frm
Case "一覧 → 詳細画面"
Build_ListDetail_WithCode frm
Case "行編集フォーム(Add/Edit/Delete)"
Build_Edit_WithCode frm
Case "ドロップダウンつき一覧 UI"
Build_DropFilter_WithCode frm
Case "高機能検索フォーム(AND/OR)"
Build_AdvSearch_WithCode frm
Case Else
MsgBox "未定義のUIタイプです: " & uiType
Exit Sub
End Select
Confirm "UI を自動生成しました: " & frm.Name
End Sub
' ---------- 1) カレンダー入力(簡易) ----------
Sub Build_Calendar_WithCode(frm As VBComponent)
Dim r As Long, c As Long, left0 As Single, top0 As Single
left0 = 10: top0 = 30
For r = 0 To 5
For c = 1 To 7
AddControlToForm frm, "Forms.Label.1", "lbl" & r & "_" & c, left0 + (c - 1) * 30, top0 + r * 22, 28, 20, ""
Next c
Next r
AddControlToForm frm, "Forms.CommandButton.1", "btnClose", 10, 170, 80, 24, "閉じる"
frm.Properties("Caption") = "カレンダー入力"
Dim code As String
code = ""
code = code & "Option Explicit" & vbCrLf
code = code & "Public SelectedDate As Date" & vbCrLf & vbCrLf
code = code & "Private Sub UserForm_Initialize()" & vbCrLf
code = code & " Dim d0 As Date, r As Long, c As Long" & vbCrLf
code = code & " d0 = DateSerial(Year(Date), Month(Date), 1)" & vbCrLf
code = code & " Dim startCol As Long: startCol = Weekday(d0, vbSunday)" & vbCrLf
code = code & " Dim dayCnt As Long: dayCnt = Day(DateSerial(Year(d0), Month(d0) + 1, 0))" & vbCrLf
code = code & " Dim cur As Long: cur = 1" & vbCrLf
code = code & " Dim rIdx As Long: rIdx = 0, cIdx As Long: cIdx = startCol" & vbCrLf
code = code & " Do While cur <= dayCnt" & vbCrLf
code = code & " Me.Controls(""lbl"" & rIdx & ""_"" & cIdx).Caption = cur" & vbCrLf
code = code & " cur = cur + 1" & vbCrLf
code = code & " cIdx = cIdx + 1" & vbCrLf
code = code & " If cIdx > 7 Then cIdx = 1: rIdx = rIdx + 1" & vbCrLf
code = code & " Loop" & vbCrLf
code = code & "End Sub" & vbCrLf & vbCrLf
code = code & "Private Sub btnClose_Click()" & vbCrLf
code = code & " Unload Me" & vbCrLf
code = code & "End Sub" & vbCrLf & vbCrLf
' Click handler for calendar labels (generic)
code = code & "Private Sub UserForm_Click()" & vbCrLf
code = code & " ' 個別ラベルのクリックは Designer で直接ハンドルできないため" & vbCrLf
code = code & " ' 必要なら個別ラベルの Click イベントを追加注入する" & vbCrLf
code = code & "End Sub" & vbCrLf
InjectFormCode frm, code
End Sub
' ---------- 2) 日付範囲ピッカー ----------
Sub Build_DateRange_WithCode(frm As VBComponent)
AddControlToForm frm, "Forms.Label.1", "lblFrom", 10, 10, 50, 18, "From"
AddControlToForm frm, "Forms.TextBox.1", "txtFrom", 70, 10, 100, 20, ""
AddControlToForm frm, "Forms.Label.1", "lblTo", 10, 40, 50, 18, "To"
AddControlToForm frm, "Forms.TextBox.1", "txtTo", 70, 40, 100, 20, ""
AddControlToForm frm, "Forms.CommandButton.1", "btnOK", 10, 80, 60, 24, "OK"
AddControlToForm frm, "Forms.CommandButton.1", "btnCancel", 80, 80, 60, 24, "Cancel"
frm.Properties("Caption") = "日付範囲ピッカー"
Dim code As String
code = ""
code = code & "Option Explicit" & vbCrLf
code = code & "Public DateFrom As Variant, DateTo As Variant" & vbCrLf & vbCrLf
code = code & "Private Sub btnOK_Click()" & vbCrLf
code = code & " If IsDate(Me.txtFrom.Value) And IsDate(Me.txtTo.Value) Then" & vbCrLf
code = code & " DateFrom = CDate(Me.txtFrom.Value)" & vbCrLf
code = code & " DateTo = CDate(Me.txtTo.Value)" & vbCrLf
code = code & " Me.Hide" & vbCrLf
code = code & " Else" & vbCrLf
code = code & " MsgBox ""日付を正しく入力してください"", vbExclamation" & vbCrLf
code = code & " End If" & vbCrLf
code = code & "End Sub" & vbCrLf & vbCrLf
code = code & "Private Sub btnCancel_Click()" & vbCrLf
code = code & " DateFrom = Empty: DateTo = Empty" & vbCrLf
code = code & " Unload Me" & vbCrLf
code = code & "End Sub" & vbCrLf
InjectFormCode frm, code
End Sub
' ---------- 3) プログレスバー ----------
Sub Build_Progress_WithCode(frm As VBComponent)
AddControlToForm frm, "Forms.Label.1", "lblBar", 10, 40, 0, 18, ""
AddControlToForm frm, "Forms.Label.1", "lblMsg", 10, 10, 200, 18, "処理中..."
frm.Properties("Caption") = "進捗"
Dim code As String
code = ""
code = code & "Option Explicit" & vbCrLf
code = code & "Public Sub Progress_Init(msg As String)" & vbCrLf
code = code & " Me.lblBar.Width = 0" & vbCrLf
code = code & " Me.lblMsg.Caption = msg" & vbCrLf
code = code & " Me.Show vbModeless" & vbCrLf
code = code & " DoEvents" & vbCrLf
code = code & "End Sub" & vbCrLf & vbCrLf
code = code & "Public Sub Progress_Set(pct As Double)" & vbCrLf
code = code & " If pct < 0 Then pct = 0" & vbCrLf
code = code & " If pct > 1 Then pct = 1" & vbCrLf
code = code & " Me.lblBar.Width = Me.InsideWidth * pct" & vbCrLf
code = code & " DoEvents" & vbCrLf
code = code & "End Sub" & vbCrLf & vbCrLf
code = code & "Public Sub Progress_Close()" & vbCrLf
code = code & " Unload Me" & vbCrLf
code = code & "End Sub" & vbCrLf
InjectFormCode frm, code
End Sub
' ---------- 4) 検索ダイアログ ----------
Sub Build_Search_WithCode(frm As VBComponent)
AddControlToForm frm, "Forms.TextBox.1", "txtKey", 10, 10, 150, 20, ""
AddControlToForm frm, "Forms.CommandButton.1", "btnSearch", 170, 10, 60, 24, "検索"
AddControlToForm frm, "Forms.ListBox.1", "lstResult", 10, 40, 220, 140, ""
frm.Properties("Caption") = "検索ダイアログ"
Dim code As String
code = ""
code = code & "Option Explicit" & vbCrLf
code = code & "Private Sub btnSearch_Click()" & vbCrLf
code = code & " Dim key As String: key = Trim(Me.txtKey.Value)" & vbCrLf
code = code & " Dim ws As Worksheet: Set ws = ThisWorkbook.Sheets(1)" & vbCrLf
code = code & " Dim c As Range" & vbCrLf
code = code & " Me.lstResult.Clear" & vbCrLf
code = code & " If key = """" Then Exit Sub" & vbCrLf
code = code & " For Each c In ws.UsedRange.Columns(1).Cells" & vbCrLf
code = code & " If InStr(1, c.Value, key, vbTextCompare) > 0 Then" & vbCrLf
code = code & " Me.lstResult.AddItem c.Address(False, False) & "" : "" & c.Value" & vbCrLf
code = code & " End If" & vbCrLf
code = code & " Next" & vbCrLf
code = code & "End Sub" & vbCrLf
InjectFormCode frm, code
End Sub
' ---------- 5) ログイン画面 ----------
Sub Build_Login_WithCode(frm As VBComponent)
AddControlToForm frm, "Forms.Label.1", "lblU", 10, 10, 60, 18, "ユーザー"
AddControlToForm frm, "Forms.TextBox.1", "txtUser", 80, 10, 120, 20, ""
AddControlToForm frm, "Forms.Label.1", "lblP", 10, 40, 60, 18, "パスワード"
AddControlToForm frm, "Forms.TextBox.1", "txtPass", 80, 40, 120, 20, ""
AddControlToForm frm, "Forms.CommandButton.1", "btnOK", 40, 80, 60, 24, "OK"
AddControlToForm frm, "Forms.CommandButton.1", "btnCancel", 120, 80, 60, 24, "Cancel"
frm.Properties("Caption") = "ログイン"
Dim code As String
code = ""
code = code & "Option Explicit" & vbCrLf
code = code & "Public LoginOK As Boolean" & vbCrLf & vbCrLf
code = code & "Private Sub btnOK_Click()" & vbCrLf
code = code & " ' 実務ではここにハッシュ比較や外部認証を入れる" & vbCrLf
code = code & " If Me.txtUser.Value = ""admin"" And Me.txtPass.Value = ""1234"" Then" & vbCrLf
code = code & " LoginOK = True: Me.Hide" & vbCrLf
code = code & " Else" & vbCrLf
code = code & " MsgBox ""認証に失敗しました"", vbExclamation" & vbCrLf
code = code & " End If" & vbCrLf
code = code & "End Sub" & vbCrLf & vbCrLf
code = code & "Private Sub btnCancel_Click()" & vbCrLf
code = code & " LoginOK = False: Unload Me" & vbCrLf
code = code & "End Sub" & vbCrLf
InjectFormCode frm, code
End Sub
' ---------- 6) 一覧 → 詳細画面 ----------
Sub Build_ListDetail_WithCode(frm As VBComponent)
AddControlToForm frm, "Forms.ListBox.1", "lst", 10, 10, 220, 150, ""
AddControlToForm frm, "Forms.CommandButton.1", "btnDetail", 240, 10, 80, 24, "詳細を見る"
frm.Properties("Caption") = "一覧"
Dim code As String
code = ""
code = code & "Option Explicit" & vbCrLf
code = code & "Private Sub UserForm_Initialize()" & vbCrLf
code = code & " Dim ws As Worksheet: Set ws = ThisWorkbook.Sheets(1)" & vbCrLf
code = code & " Dim r As Range" & vbCrLf
code = code & " Me.lst.Clear" & vbCrLf
code = code & " For Each r In ws.UsedRange.Rows" & vbCrLf
code = code & " Me.lst.AddItem r.Cells(1, 1).Value" & vbCrLf
code = code & " Next" & vbCrLf
code = code & "End Sub" & vbCrLf & vbCrLf
code = code & "Private Sub btnDetail_Click()" & vbCrLf
code = code & " If Me.lst.ListIndex < 0 Then Exit Sub" & vbCrLf
code = code & " Dim idx As Long: idx = Me.lst.ListIndex + 1" & vbCrLf
code = code & " Dim frmD As UserForm" & vbCrLf
code = code & " ' シンプルに MsgBox で詳細表示(実務では別フォームを用意)" & vbCrLf
code = code & " MsgBox ""行: "" & idx & Chr(10) & ""値: "" & ThisWorkbook.Sheets(1).Cells(idx, 1).Value" & vbCrLf
code = code & "End Sub" & vbCrLf
InjectFormCode frm, code
End Sub
' ---------- 7) 行編集フォーム(Add/Edit/Delete) ----------
Sub Build_Edit_WithCode(frm As VBComponent)
Dim i As Long
Dim labels As Variant: labels = Array("ID", "名前", "数量")
For i = 0 To 2
AddControlToForm frm, "Forms.Label.1", "lbl" & i, 10, 10 + i * 30, 40, 18, labels(i)
AddControlToForm frm, "Forms.TextBox.1", "txt" & i, 60, 10 + i * 30, 120, 20, ""
Next i
AddControlToForm frm, "Forms.CommandButton.1", "btnAdd", 200, 10, 80, 24, "追加"
AddControlToForm frm, "Forms.CommandButton.1", "btnEdit", 200, 45, 80, 24, "更新"
AddControlToForm frm, "Forms.CommandButton.1", "btnDel", 200, 80, 80, 24, "削除"
frm.Properties("Caption") = "行編集"
Dim code As String
code = ""
code = code & "Option Explicit" & vbCrLf
code = code & "Private Sub btnAdd_Click()" & vbCrLf
code = code & " Dim r As Long: r = ThisWorkbook.Sheets(1).Cells(Rows.Count, 1).End(xlUp).Row + 1" & vbCrLf
code = code & " With ThisWorkbook.Sheets(1)" & vbCrLf
code = code & " .Cells(r, 1).Value = Me.txt0.Value" & vbCrLf
code = code & " .Cells(r, 2).Value = Me.txt1.Value" & vbCrLf
code = code & " .Cells(r, 3).Value = Me.txt2.Value" & vbCrLf
code = code & " End With" & vbCrLf
code = code & " MsgBox ""追加しました""" & vbCrLf
code = code & "End Sub" & vbCrLf & vbCrLf
code = code & "Private Sub btnEdit_Click()" & vbCrLf
code = code & " Dim f As Range" & vbCrLf
code = code & " Set f = ThisWorkbook.Sheets(1).Columns(1).Find(What:=Me.txt0.Value, LookAt:=xlWhole)" & vbCrLf
code = code & " If f Is Nothing Then MsgBox ""IDが見つかりません"": Exit Sub" & vbCrLf
code = code & " f.Offset(0, 1).Value = Me.txt1.Value" & vbCrLf
code = code & " f.Offset(0, 2).Value = Me.txt2.Value" & vbCrLf
code = code & " MsgBox ""更新しました""" & vbCrLf
code = code & "End Sub" & vbCrLf & vbCrLf
code = code & "Private Sub btnDel_Click()" & vbCrLf
code = code & " Dim f As Range" & vbCrLf
code = code & " Set f = ThisWorkbook.Sheets(1).Columns(1).Find(What:=Me.txt0.Value, LookAt:=xlWhole)" & vbCrLf
code = code & " If f Is Nothing Then MsgBox ""IDが見つかりません"": Exit Sub" & vbCrLf
code = code & " f.EntireRow.Delete" & vbCrLf
code = code & " MsgBox ""削除しました""" & vbCrLf
code = code & "End Sub" & vbCrLf
InjectFormCode frm, code
End Sub
' ---------- 8) ドロップダウンつき一覧 ----------
Sub Build_DropFilter_WithCode(frm As VBComponent)
AddControlToForm frm, "Forms.ComboBox.1", "cmb", 10, 10, 140, 20, ""
AddControlToForm frm, "Forms.ListBox.1", "lst", 10, 40, 260, 140, ""
frm.Properties("Caption") = "ドロップダウン一覧"
Dim code As String
code = ""
code = code & "Option Explicit" & vbCrLf
code = code & "Private Sub UserForm_Initialize()" & vbCrLf
code = code & " Dim ws As Worksheet: Set ws = ThisWorkbook.Sheets(1)" & vbCrLf
code = code & " Dim col As Collection: Set col = New Collection" & vbCrLf
code = code & " Dim r As Range" & vbCrLf
code = code & " On Error Resume Next" & vbCrLf
code = code & " For Each r In ws.UsedRange.Columns(2).Cells" & vbCrLf
code = code & " col.Add r.Value, CStr(r.Value)" & vbCrLf
code = code & " Next" & vbCrLf
code = code & " On Error GoTo 0" & vbCrLf
code = code & " Dim v" & vbCrLf
code = code & " For Each v In col" & vbCrLf
code = code & " Me.cmb.AddItem v" & vbCrLf
code = code & " Next" & vbCrLf
code = code & " Call FillList(Empty)" & vbCrLf
code = code & "End Sub" & vbCrLf & vbCrLf
code = code & "Private Sub cmb_Change()" & vbCrLf
code = code & " Call FillList(Me.cmb.Value)" & vbCrLf
code = code & "End Sub" & vbCrLf & vbCrLf
code = code & "Private Sub FillList(filterVal As Variant)" & vbCrLf
code = code & " Dim ws As Worksheet: Set ws = ThisWorkbook.Sheets(1)" & vbCrLf
code = code & " Dim r As Range" & vbCrLf
code = code & " Me.lst.Clear" & vbCrLf
code = code & " For Each r In ws.UsedRange.Rows" & vbCrLf
code = code & " If filterVal = Empty Or r.Cells(1, 2).Value = filterVal Then" & vbCrLf
code = code & " Me.lst.AddItem r.Cells(1, 1).Value" & vbCrLf
code = code & " End If" & vbCrLf
code = code & " Next" & vbCrLf
code = code & "End Sub" & vbCrLf
InjectFormCode frm, code
End Sub
' ---------- 9) 高機能検索フォーム(AND/OR) ----------
Sub Build_AdvSearch_WithCode(frm As VBComponent)
AddControlToForm frm, "Forms.TextBox.1", "txt1", 10, 10, 110, 20, ""
AddControlToForm frm, "Forms.TextBox.1", "txt2", 130, 10, 110, 20, ""
AddControlToForm frm, "Forms.OptionButton.1", "optAnd", 10, 40, 60, 18, "AND"
AddControlToForm frm, "Forms.OptionButton.1", "optOr", 80, 40, 60, 18, "OR"
AddControlToForm frm, "Forms.CommandButton.1", "btnSearch", 10, 70, 60, 24, "検索"
AddControlToForm frm, "Forms.ListBox.1", "lst", 10, 100, 230, 140, ""
frm.Properties("Caption") = "高機能検索"
Dim code As String
code = ""
code = code & "Option Explicit" & vbCrLf
code = code & "Private Sub btnSearch_Click()" & vbCrLf
code = code & " Dim k1 As String: k1 = Trim(Me.txt1.Value)" & vbCrLf
code = code & " Dim k2 As String: k2 = Trim(Me.txt2.Value)" & vbCrLf
code = code & " Dim ANDmode As Boolean: ANDmode = Me.optAnd.Value" & vbCrLf
code = code & " Dim ws As Worksheet: Set ws = ThisWorkbook.Sheets(1)" & vbCrLf
code = code & " Dim r As Range" & vbCrLf
code = code & " Me.lst.Clear" & vbCrLf
code = code & " For Each r In ws.UsedRange.Rows" & vbCrLf
code = code & " Dim v As String: v = CStr(r.Cells(1, 1).Value)" & vbCrLf
code = code & " Dim ok As Boolean" & vbCrLf
code = code & " If ANDmode Then" & vbCrLf
code = code & " ok = (k1 <> """" And InStr(1, v, k1, vbTextCompare) > 0) And (k2 <> """" And InStr(1, v, k2, vbTextCompare) > 0)" & vbCrLf
code = code & " Else" & vbCrLf
code = code & " ok = (k1 <> """" And InStr(1, v, k1, vbTextCompare) > 0) Or (k2 <> """" And InStr(1, v, k2, vbTextCompare) > 0)" & vbCrLf
code = code & " End If" & vbCrLf
code = code & " If ok Then Me.lst.AddItem v" & vbCrLf
code = code & " Next" & vbCrLf
code = code & "End Sub" & vbCrLf
InjectFormCode frm, code
End Sub
' ---------- Optional: Simple UI generator form runner ----------
Sub ShowGeneratorSimple()
Dim s As String
s = InputBox("生成する UI を入力してください(例: カレンダー入力、プログレスバー、検索ダイアログ、ログイン画面、一覧 → 詳細画面、行編集フォーム(Add/Edit/Delete)、ドロップダウンつき一覧 UI、高機能検索フォーム(AND/OR))", "UI生成")
If s = "" Then Exit Sub
BuildUI_WithCode s
End Sub
VB使い方(ステップ・バイ・ステップ)
- Excel の開発タブ → Visual Basic を開く。
- 新しい標準モジュールを作り、上記コードを丸ごと貼る。
- 「ファイル」→「オプション」→「セキュリティセンター」→「マクロの設定」→「VBA プロジェクト オブジェクト モデルへのアクセスを信頼する」にチェックを入れる。
ShowGeneratorSimpleを実行すると、生成したい UI 名を入力するダイアログが表示されます。例:検索ダイアログと入力すると、UserFormUI_yyyymmdd_hhmmssが作成され、検索用のコントロールと動作コードが注入されます。- 作成された Form は VBA エディタで開き、デザインやコードを微調整して使ってください。
生成後のカスタマイズ案(実務向け)
- 権限・認証の差し替え:ログイン画面の認証ロジックをHash/AD/DB呼び出しに変更。
- カレンダーのクリックイベント:ラベルごとの Click を注入して選択処理を追加(必要なら更に自動生成可能)。
- テンプレの外部化:頻繁に使う共通関数(データ参照/バリデーション)を別モジュールにまとめ、生成コードから呼ぶようにして保守性を向上。
- リボン連携:生成ツール自体をリボンボタンで呼べるようにすれば、利用者に優しい。
例:実際に「検索ダイアログ」を生成して試す
ShowGeneratorSimpleを実行 → プロンプトで検索ダイアログと入力。- 作成されたフォームを実行(F5) → テキストに検索語を入れて「検索」ボタンを押すと、シートの1列目から部分一致でヒット結果が listbox に追加されます。
トラブルシューティング(よくある問題)
- VBProject へのアクセス拒否:セキュリティ設定(信頼)を確認してください。
- 同名コンポーネントが残る:既に同名コンポーネントがあると追加に失敗することがあるため、コード内で既存を削除する処理を入れています。
- デザイン調整が必要:自動レイアウトは基本形です。最終的にはIDEで細かく配置してください。

