atsamd_hal/peripherals/clock/d5x/
v2.rs

1//! # Version 2 of the `clock` module
2//!
3//! ## Overview
4//!
5//! This module provides a simple, ergonomic, and most of all **safe** API to
6//! create and manage the clock tree in ATSAMD5x and E5x devices. It uses
7//! [type-level programming techniques](crate::typelevel) to prevent users from
8//! creating invalid or unsound clocking configurations.
9//!
10//! <p style="background:rgba(255,181,77,0.16);padding:0.75em;">
11//! <strong> Note: </strong> Using a type-level API does place some limitations
12//! on how the clocks can be configured. The types must be checked at
13//! compile-time, which means the state of a given clock must also be known at
14//! compile-time. This is exceedingly reasonable for most clocking
15//! configurations, because most users set up their clocks once and never change
16//! them again. However, if you need to dynamically change the clocking
17//! configuration at run-time, you may find this API less ergonomic. A future,
18//! fully dynamic API has been discussed, but nothing has been developed so far.
19//! </p>
20//!
21//! The sections that follow provide an explanation of key concepts in the
22//! module. We highly recommend users read through them to better understand the
23//! `clock` module API. A [complete example](self#getting-started) is also
24//! provided.
25//!
26//! ## Clock safety
27//!
28//! A clock tree represents dependencies among clocks, where producer clocks
29//! feed consumer clocks. Root clocks are the original producers, as they are
30//! derived from oscillators or external clocks. Branch clocks are both
31//! producers and consumers, since they modify and distribute clocks. And leaf
32//! clocks are consumers only; they drive peripherals or external clock outputs
33//! but do not feed other clocks.
34//!
35//! To safely create and use a clock tree, it is critical that producer clocks
36//! not be modified or disabled while their consumer clocks are still in active
37//! use. Stated differently, if clock `B` consumes clock `A`, then clock `A`
38//! **must not** be modified or disabled while clock `B` is still in use.
39//!
40//! Notice that this requirement mimics the principle of "aliased XOR mutable"
41//! underlying the Rust borrow checker. A producer clock can only be modified if
42//! it is not "borrowed" (consumed) by any other clocks.
43//!
44//! The following sections will review the various type-level programming
45//! techniques used to enforce this principle in the `clock` module.
46//!
47//! ## Clock state machines
48//!
49//! Each available clock is represented in Rust as a unique, singleton object.
50//! Users cannot create two instances of the same clock without using `unsafe`.
51//!
52//! However, a given clock is not always represented with the same **type**.
53//! Specifically, each clock has at least two representations, one for the
54//! configured and enabled clock, and another for the unconfigured and disabled
55//! clock.
56//!
57//! These states are represented in Rust using distinct types, forming a
58//! type-level state machine. Moreover, the disabled state is always represented
59//! by a `Token` type. As the name implies, `Token`s have no functionality on
60//! their own; they can only be exchanged for a different type representing
61//! another state.
62//!
63//! ## Clock relationships
64//!
65//! In general, there are two classes of clock in ATSAMD chips. Some clocks map
66//! one-to-one (1:1) to a specific bus or peripheral. This is true for the AHB
67//! clocks ([`AhbClk`]s), APB clocks ([`ApbClk`]s), GCLK outputs ([`GclkOut`]s),
68//! peripheral channel clocks ([`Pclk`]s), and RTC oscillator ([`RtcOsc`]).
69//! Other clocks form one-to-many (1:N) relationships, like the external crystal
70//! oscillator ([`Xosc`]), the 48 MHz DFLL ([`Dfll`]) or the two DPLLs
71//! ([`Dpll`]).
72//!
73//! The `clock` module uses a distinct approach for each class.
74//!
75//! ### 1:1 clocks
76//!
77//! One-to-one relationships are easily modelled in Rust using move semantics.
78//! For example, an enabled peripheral channel clock is represented as a
79//! [`Pclk`] object. The respective peripheral API can move the `Pclk` and take
80//! ownership of it. In that case, the `Pclk` acts as proof that the peripheral
81//! clock is enabled, and the transfer of ownership prevents users from
82//! modifying or disabling the `Pclk` while it is in use by the peripheral.
83//!
84//! One-to-one clocks generally have little to no configuration. They are
85//! typically converted directly from disabled `Token` types to fully enabled
86//! clock types. For example, the `Pclk` type has only two methods,
87//! [`Pclk::enable`] and [`Pclk::disable`], which convert [`PclkToken`]s to
88//! `Pclk`s and vice versa.
89//!
90//! ### 1:N clocks
91//!
92//! One-to-many relationships are more difficult to model in Rust.
93//!
94//! As discussed above, we are trying to create something akin to "aliased XOR
95//! mutable", where producer clocks cannot be modified while used by consumer
96//! clocks. A natural approach would be to use the Rust borrow checker directly.
97//! In that case, consumer clocks would hold `&Producer` references to the
98//! `Producer` clock object. The existence of outstanding shared borrows would
99//! naturally prevent users from calling `Producer` methods taking `&mut self`.
100//!
101//! Unfortunately, while this approach could work, there is a critical problem
102//! with disastrous consequences for ergonomics. To satisfy the Rust borrow
103//! checker, `Producer` clock objects *could not be moved* while `&Producer`
104//! references were still held by consumer clocks.
105//!
106//! However, this restriction is unnecessary. A `Producer` clock object is
107//! merely a semantic object representing the "idea" of a producer clock. And
108//! "borrowing" the producer is not meant to protect memory from corruption.
109//! Rather, our goal is only to restrict the `Producer` API, to prevent it from
110//! being modified or disabled once it has been connected to a consumer. We
111//! don't need to permanently hold the `Producer` object in place to do that.
112//!
113//! It is possible to build a `clock` API based on the borrow checker, but it
114//! would be extremely frustrating to use in practice, because of restrictions
115//! on the movement of `Producer` objects.
116//!
117//! Instead, the `clock` module takes a different approach. It uses type-level
118//! programming to track, at compile-time, the number of consumer clocks, N,
119//! fed by a particular producer clock. With this approach, we can move
120//! `Producer` objects while still making them impossible to modify if N > 0.
121//!
122//! The following sections will describe the implementation of this strategy.
123//!
124//! ## Tracking N at compile-time for 1:N clocks
125//!
126//! We have two specific goals. We need to both track the number of consumer
127//! clocks, N, that are actively using a given producer clock. And we need to
128//! restrict the producer clock API when N > 0.
129//!
130//! ### A compile-time counter
131//!
132//! First, we need to develop some way to track the number of consumer clocks,
133//! N, within the type system. To accomplish this, we need both a way to
134//! represent N in the type system and a way to increase or decrease N when
135//! making or breaking connections in the clock tree.
136//!
137//! To represent N, we can use type-level, [`Unsigned`] integers from the
138//! [`typenum`] crate (i.e. [`U0`], [`U1`], etc). And we can use a type
139//! *parameter*, `N`, to represent some unknown, type-level number.
140//!
141//! Next, we need a way to increase or decrease the type parameter `N`. The
142//! [`typenum`] crate provides type aliases [`Add1`] and [`Sub1`] that map from
143//! each [`Unsigned`] integer to its successor and predecessor types,
144//! respectively. We can leverage these to create our own type with a counter
145//! that we [`Increment`] or [`Decrement`] at compile-time. These two traits
146//! form the foundation for our strategy for handling 1:N clocks in this module.
147//!
148//! ### The `Enabled` wrapper
149//!
150//! Our representation of a 1:N producer clock is [`Enabled<T, N>`], which is a
151//! wrapper struct that pairs some *enabled* clock type `T` with a type `N`
152//! representing a consumer count. The wrapper restricts access to the
153//! underlying clock type, `T`, allowing us to selectively define methods when
154//! `N = U0`, that is, when there are no consumers of a given producer clock.
155//!
156//! The [`Enabled`] type itself implements [`Increment`] and [`Decrement`] as
157//! well, which allows type-level transformations to increment or decrement the
158//! counter, e.g. `Enabled<T, U0>` to `Enabled<T, U1>`. Such transformations can
159//! only be performed within the HAL; so users cannot change the consumer count
160//! arbitrarily.
161//!
162//! ### Acting as a clock `Source`
163//!
164//! Finally, we need to define some generic interface for interacting with 1:N
165//! producer clocks. However, when designing this interface, we need to be
166//! careful not to lose information during type-level transformations.
167//!
168//! In particular, the `Enabled` counter type alone is not enough for proper
169//! clock safety. If we used consumer `A` to `Increment` producer `P` from
170//! `Enabled<P, U0>` to `Enabled<P, U1>`, but then used consumer `B` to
171//! `Decrement` the producer back to `Enabled<P, U0>`, we would leave consumer
172//! `A` dangling.
173//!
174//! To solve this problem, we need some way to guarantee that a given consumer
175//! can only `Decrement` the same producer it `Increment`ed. Stated differently,
176//! we need a way to track the identity of each consumer's clock source.
177//!
178//! The [`Source`] trait is designed for this purpose. It marks
179//! [`Enabled<T, N>`] producer clocks, and it's associated type, [`Id`], is the
180//! identity type that should be stored by consumers.
181//!
182//! Given that all implementers of `Source` are instances of `Enabled<T, N>`,
183//! the naïve choice for [`Source::Id`] would be `T`. However, in a moment, we
184//! will see why this choice is not ideal.
185//!
186//! ### `Id` types
187//!
188//! Many of the clock types in this module have additional type parameters that
189//! track the clock's configuration. For instance, [`Xosc0<M>`] represents one
190//! of the external crystal oscillators. Here, the type parameter `M` represents
191//! the XOSC's [`Mode`](xosc::Mode), which can either be [`CrystalMode`] or
192//! [`ClockMode`]. Accordingly, methods to adjust the crystal current, etc. are
193//! only available on `Xosc0<CrystalMode>`.
194//!
195//! While these type parameters are important and necessary for configuration of
196//! a given producer clock, they are not relevant to consumer clocks. A consumer
197//! clock does not need to know or care which `Mode` the XOSC is using, but
198//! it *does* need to track that its clock [`Source`] is XOSC0.
199//!
200//! From this, we can see that `Enabled<Xosc0<M>, N>` should not implement
201//! `Source` with `Source::Id = Xosc0<M>`, because that would require consumers
202//! to needlessly track the XOSC `Mode`.
203//!
204//! Instead, this module defines a series of `Id` types representing the
205//! *identity* of a given clock, rather than the clock itself. This is like the
206//! distinction between a passport and a person. A passport identifies a person,
207//! regardless of changes to their clothes or hair. The `Id` types serve to
208//! erase configuration information, representing only the clock's identity.
209//!
210//! For `Xosc0<M>`, the corresponding `Id` type is [`Xosc0Id`]. Thus,
211//! `Enabled<Xosc0<M>, N>` implements `Source` with `Source::Id = Xosc0Id`.
212//!
213//! ## Notes on memory safety
214//!
215//! ### Register interfaces
216//!
217//! Although HAL users see `Token` types as merely opaque objects, internally
218//! they serve a dual purpose as the primary register interface to control the
219//! corresponding clock. Moreover, they also fundamentally restructure the way
220//! registers are accessed relative to the [PAC].
221//!
222//! Each of the four PAC clocking structs ([`OSCCTRL`], [`OSC32KCTRL`], [`GCLK`]
223//! and [`MCLK`]) is a singleton object that controls a set of MMIO registers.
224//! It is impossible to create two instances of any PAC object without `unsafe`.
225//! However, each object controls a large set of registers that can be further
226//! sub-divided into smaller sets for individual clocks. For example, the
227//! [`GCLK`] object controls registers for 12 different clock generators and 48
228//! peripheral channel clocks.
229//!
230//! `Token` types serve to break up the large PAC objects into smaller,
231//! more-targetted pieces. And in the process, they also remove the PAC objects'
232//! [interior mutability]. But this is only possible because each `Token` is
233//! *also* a singleton, and because individual clocks are configured through
234//! *mutually exclusive* sets of registers.
235//!
236//! ### Bus clocks
237//!
238//! Bus clocks are fundamentally different from the other clock types in this
239//! module, because they do not use mutually exclusive registers for
240//! configuration. For instance, the registers that control [`Dpll0`] are
241//! mutually exclusive to those that control [`Dpll1`], but `ApbClk<Sercom0>`
242//! and `ApbClk<Sercom1>` share a single register.
243//!
244//! This presents a challenge for memory safety, because we need some way to
245//! guarantee that there are no data races. For example, if both
246//! `ApbClk<Sercom0>` and `ApbClk<Sercom1>` tried to modify the `APBAMASK`
247//! register from two different execution contexts, a read/modify/write
248//! operation could be preempted, leading to memory corruption.
249//!
250//! To prevent data races when controlling bus clocks, we introduce two new
251//! types to mediate access to the shared registers. For [`AhbClk`]s, this is
252//! the [`Ahb`] type; and for [`ApbClk`]s, this is the [`Apb`] type. In a sense,
253//! the `Ahb` and `Apb` types represent the actual corresponding buses. Thus,
254//! enabling an APB clock by converting an [`ApbToken`] into an `ApbClk`
255//! requires exclusive access to the `Apb` in the form of `&mut Apb`.
256//!
257//! ## Getting started
258//!
259//! To set up a clock tree, start by trading the [PAC](crate::pac)-level
260//! clocking structs for their HAL equivalents. Right now, the only way to do so
261//! safely is using the [`clock_system_at_reset`] function, which assumes all
262//! clocks are in their default state at power-on reset. If this is not the
263//! case, because, for example, a bootloader has modified the clocks, then you
264//! may need to manually create the matching configuration using `unsafe` code.
265//!
266//! ```no_run
267//! use atsamd_hal::clock::v2::clock_system_at_reset;
268//! use atsamd_hal::pac::Peripherals;
269//! let mut pac = Peripherals::take().unwrap();
270//! let (buses, clocks, tokens) = clock_system_at_reset(
271//!     pac.OSCCTRL,
272//!     pac.OSC32KCTRL,
273//!     pac.GCLK,
274//!     pac.MCLK,
275//!     &mut pac.NVMCTRL,
276//! );
277//! ```
278//!
279//! At this point, you may notice that the function returned three different
280//! objects, the [`Buses`], [`Clocks`] and [`Tokens`].
281//!
282//! The [`Buses`] struct contains the [`Ahb`] and [`Apb`] objects, which
283//! represent the corresponding AHB and APB buses. See the [notes on memory
284//! safety](self#notes-on-memory-safety) for more details on these types.
285//!
286//! The [`Clocks`] struct contains all of the clocks that are enabled and
287//! running at power-on reset, specifically:
288//! - All of the [`AhbClks`]
289//! - Some of the [`ApbClks`]
290//! - The 48 MHz [`Dfll`], running in open-loop mode, represented as as
291//!   `Enabled<Dfll, U1>`. `N = U1` here because [`Gclk0`] consumes it. See
292//!   [above](self#tracking-n-at-compile-time-for-1n-clocks) for details on
293//!   [`Enabled<T, N>`].
294//! - [`Gclk0`], sourced by the `Dfll` and represented as
295//!   `Enabled<Gclk0<DfllId>, U1>`. Note the use of [`DfllId`] as an [`Id`
296//!   type](self#id-types) here. Although `Gclk0` is not consumed by any clock
297//!   represented in this module, it *is* consumed by the processor's main
298//!   clock. We represent this by setting `N = U1`, which we use to restrict the
299//!   available API. Specifically, [`EnabledGclk0`] has special methods not
300//!   available to other [`Gclk`]s.
301//! - The [`OscUlp32kBase`] clock, which can act as a [`Source`] for the
302//!   [`OscUlp1k`] and [`OscUlp32k`] clocks. It has no consumers at power-on
303//!   reset, so it is represented as `Enabled<OscUlp32kBase, U0>`. However, it
304//!   can never be disabled, so we provide no `.disable()` method.
305//!
306//! The [`Tokens`] struct contains all of the available `Token`s, which
307//! [represent clocks that are disabled](self#clock-state-machines) at power-on
308//! reset. Each `Token` can be exchanged for a corresponding clock object.
309//!
310//! ## Example clock tree
311//!
312//! Finally, we will walk through the creation of a simple clock tree to
313//! illustrate some of the remaining concepts inherent to this module.
314//!
315//! Starting from the previous snippet, we have the [`Buses`], [`Clocks`] and
316//! [`Tokens`] to work with, and our clock tree at power-on reset looks like
317//! this.
318//!
319//! ```text
320//! DFLL (48 MHz)
321//! └── GCLK0 (48 MHz)
322//!     └── Main clock (48 MHz)
323//! ```
324//!
325//! Our goal will be a clock tree that looks like this:
326//!
327//! ```text
328//! XOSC0 (8 MHz)
329//! └── DPLL0 (100 MHz)
330//!     └── GCLK0 (100 MHz)
331//!         ├── Main clock (100 MHz)
332//!         ├── SERCOM0 peripheral clock
333//!         └── Output to GPIO pin
334//! ```
335//!
336//! We will use an external crystal oscillator running at 8 MHz to feed a DPLL,
337//! which will increase the clock frequency to 100 MHz. Then, we will
338//! reconfigure GCLK0 to use the 100 MHz DPLL clock instead of the 48 MHz DFLL
339//! clock.
340//!
341//! First, let's import some of the necessary types. We will see what each type
342//! represents in turn.
343//!
344//! ```no_run
345//! use atsamd_hal::{
346//!     clock::v2::{
347//!         clock_system_at_reset,
348//!         dpll::Dpll,
349//!         pclk::Pclk,
350//!         xosc::Xosc,
351//!     },
352//!     gpio::Pins,
353//!     pac::Peripherals,
354//!     time::U32Ext,
355//! };
356//! ```
357//!
358//! To create an instance of [`Xosc`], we will first need to identify which of
359//! the two XOSC clocks we will use. Suppose an external crystal is attached to
360//! pins `PA14` and `PA15`. These pins feed the XOSC0 clock, so we will want to
361//! create an instance of [`Xosc0`]. Note that `Xosc0<M>` is merely an alias for
362//! `Xosc<Xosc0Id, M>`. Here, [`Xosc0Id`] represents the
363//! [*identity*](self#id-types) of the XOSC0 clock, rather than the clock
364//! itself, and `M` represents the XOSC [`Mode`](xosc::Mode).
365//!
366//! Next, we access the [`Tokens`] struct to extract the corresponding
367//! [`XoscToken`] for XOSC0, and we trade the PAC `PORT` struct for the
368//! [`gpio::Pins`] struct to access the GPIO pins. We can then call
369//! [`Xosc::from_crystal`] to trade the token and [`Pin`]s to yield an instance
370//! of [`Xosc0`]. In doing so, we also provide the oscillator frequency.
371//!
372//! Finally, we can chain a call to the [`Xosc::enable`] method to enable the
373//! XOSC and return an instance of [`EnabledXosc0<M, N>`], which is simply an
374//! alias for `Enabled<Xosc0<M>, N>`. In this case, we get
375//! `EnabledXosc0<CrystalMode, U0>`.
376//!
377//! ```no_run
378//! # use atsamd_hal::{
379//! #     clock::v2::{
380//! #         clock_system_at_reset,
381//! #         xosc::Xosc,
382//! #     },
383//! #     gpio::Pins,
384//! #     pac::Peripherals,
385//! #     time::U32Ext,
386//! # };
387//! # let mut pac = Peripherals::take().unwrap();
388//! # let (buses, clocks, tokens) = clock_system_at_reset(
389//! #     pac.OSCCTRL,
390//! #     pac.OSC32KCTRL,
391//! #     pac.GCLK,
392//! #     pac.MCLK,
393//! #     &mut pac.NVMCTRL,
394//! # );
395//! let pins = Pins::new(pac.PORT);
396//! let xosc0 = Xosc::from_crystal(
397//!     tokens.xosc0,
398//!     pins.pa14,
399//!     pins.pa15,
400//!     8.mhz(),
401//! ).enable();
402//! ```
403//!
404//! Next, we want to use a DPLL to multiply the 8 MHz crystal clock up to 100
405//! MHz. Once again, we need to decide between two instances of a clock, because
406//! each chip has two [`Dpll`]s. This time, however, our decision between
407//! [`Dpll0`] and [`Dpll1`] is arbitrary.
408//!
409//! Also note that, like before, `Dpll0<I>` and `Dpll1<I>` are aliases for
410//! `Dpll<Dpll0Id, I>` and `Dpll<Dpll1Id, I>`. [`Dpll0Id`] and [`Dpll1Id`]
411//! represent the *identity* of the respective DPLL, while `I` represents the
412//! [`Id` type](self#id-types) for the [`Source`] driving the DPLL. In this
413//! particular case, we aim to create an instance of `Dpll0<Xosc0Id>`.
414//!
415//! Only certain clocks can drive the DPLL, so `I` is constrained by the
416//! [`DpllSourceId`] trait. Specifically, only the [`Xosc0Id`], [`Xosc1Id`],
417//! [`Xosc32kId`] and [`GclkId`] types implement this trait.
418//!
419//! As before, we access the [`Tokens`] struct and use the corresponding
420//! [`DpllToken`] when creating an instance of `Dpll`. However, unlike before,
421//! we are creating a new clock-tree relationship that must be tracked by the
422//! type system. Because DPLL0 will now consume XOSC0, we must [`Increment`]
423//! the [`Enabled`] counter for [`EnabledXosc0`].
424//!
425//! Thus, to create an instance of `Dpll0<XoscId0>`, we must provide the
426//! `EnabledXosc0`, so that its `U0` type parameter can be incremented to `U1`.
427//! The `Dpll::from_xosc` method takes ownership of the `EnabledXosc0` and
428//! returns it with this modified type parameter.
429//!
430//! This is the essence of clock safety in this module. Once the counter type
431//! has been incremeneted to `U1`, the `EnabledXosc0` can no longer be modified
432//! or disabled. All further code can guarantee this invariant is upheld. To
433//! modify the `EnabledXosc0`, we would first have to use `Dpll::free_source` to
434//! disable the DPLL and [`Decrement`] the counter back to `U0`.
435//!
436//! ```no_run
437//! # use atsamd_hal::{
438//! #     clock::v2::{
439//! #         clock_system_at_reset,
440//! #         dpll::Dpll,
441//! #         xosc::Xosc,
442//! #     },
443//! #     gpio::Pins,
444//! #     pac::Peripherals,
445//! #     time::U32Ext,
446//! # };
447//! # let mut pac = Peripherals::take().unwrap();
448//! # let (buses, clocks, tokens) = clock_system_at_reset(
449//! #     pac.OSCCTRL,
450//! #     pac.OSC32KCTRL,
451//! #     pac.GCLK,
452//! #     pac.MCLK,
453//! #     &mut pac.NVMCTRL,
454//! # );
455//! # let pins = Pins::new(pac.PORT);
456//! # let xosc0 = Xosc::from_crystal(
457//! #     tokens.xosc0,
458//! #     pins.pa14,
459//! #     pins.pa15,
460//! #     8.mhz(),
461//! # ).enable();
462//! let (dpll0, xosc0) = Dpll::from_xosc(tokens.dpll0, xosc0);
463//! ```
464//! Next, we set the DPLL pre-divider and loop divider. We must pre-divide
465//! the XOSC clock down from 8 MHz to 2 MHz, so that it is within the valid
466//! input frequency range for the DPLL. Then, we set the DPLL loop divider, so
467//! that it will multiply the 2 MHz clock by 50 for a 100 MHz output. We do not
468//! need fractional mutiplication here, so the fractional loop divider is zero.
469//! Finally, we can enable the `Dpll`, yielding an instance of
470//! `EnabledDpll0<XoscId0>`.
471//!
472//! ```no_run
473//! # use atsamd_hal::{
474//! #     clock::v2::{
475//! #         clock_system_at_reset,
476//! #         dpll::Dpll,
477//! #         xosc::Xosc,
478//! #     },
479//! #     gpio::Pins,
480//! #     pac::Peripherals,
481//! #     time::U32Ext,
482//! # };
483//! # let mut pac = Peripherals::take().unwrap();
484//! # let (buses, clocks, tokens) = clock_system_at_reset(
485//! #     pac.OSCCTRL,
486//! #     pac.OSC32KCTRL,
487//! #     pac.GCLK,
488//! #     pac.MCLK,
489//! #     &mut pac.NVMCTRL,
490//! # );
491//! # let pins = Pins::new(pac.PORT);
492//! # let xosc0 = Xosc::from_crystal(
493//! #     tokens.xosc0,
494//! #     pins.pa14,
495//! #     pins.pa15,
496//! #     8.mhz(),
497//! # ).enable();
498//! # let (dpll0, xosc0) = Dpll::from_xosc(tokens.dpll0, xosc0);
499//! let dpll0 = dpll0.prediv(4).loop_div(50, 0).enable();
500//! ```
501//!
502//! So far, our clock tree looks like this
503//!
504//! ```text
505//! DFLL (48 MHz)
506//! └── GCLK0 (48 MHz)
507//!     └── Main clock (48 MHz)
508//!
509//! XOSC0 (8 MHz)
510//! └── DPLL0 (100 MHz)
511//! ```
512//!
513//! Our next task will be to swap GCLK0 from the 48 MHz DFLL to the 100 MHz
514//! DPLL. To do that, we will use the special [`swap_sources`] method on
515//! [`EnabledGclk0`] to change the base clock without disabling GCLK0 or the
516//! main clock.
517//!
518//! This time we will be modifying two [`Enabled`] counters simultaneously.
519//! We will [`Decrement`] the [`EnabledDfll`] count from `U1` to `U0`, and
520//! we will [`Increment`] the [`EnabledDpll0`] count from `U0` to `U1`.
521//! Again, we need to provide both the DFLL and DPLL clocks, so that their
522//! type parameters can be changed.
523//!
524//! ```no_run
525//! # use atsamd_hal::{
526//! #     clock::v2::{
527//! #         clock_system_at_reset,
528//! #         dpll::Dpll,
529//! #         xosc::Xosc,
530//! #     },
531//! #     gpio::Pins,
532//! #     pac::Peripherals,
533//! #     time::U32Ext,
534//! # };
535//! # let mut pac = Peripherals::take().unwrap();
536//! # let (buses, clocks, tokens) = clock_system_at_reset(
537//! #     pac.OSCCTRL,
538//! #     pac.OSC32KCTRL,
539//! #     pac.GCLK,
540//! #     pac.MCLK,
541//! #     &mut pac.NVMCTRL,
542//! # );
543//! # let pins = Pins::new(pac.PORT);
544//! # let xosc0 = Xosc::from_crystal(
545//! #     tokens.xosc0,
546//! #     pins.pa14,
547//! #     pins.pa15,
548//! #     8.mhz(),
549//! # ).enable();
550//! # let (dpll0, xosc0) = Dpll::from_xosc(tokens.dpll0, xosc0);
551//! # let dpll0 = dpll0.prediv(4).loop_div(50, 0).enable();
552//! let (gclk0, dfll, dpll0) = clocks.gclk0.swap_sources(clocks.dfll, dpll0);
553//! ```
554//!
555//! At this point, the DFLL is completely unused, so it can be disbled and
556//! deconstructed, leaving only the [`DfllToken`].
557//!
558//! ```no_run
559//! # use atsamd_hal::{
560//! #     clock::v2::{
561//! #         clock_system_at_reset,
562//! #         dpll::Dpll,
563//! #         xosc::Xosc,
564//! #     },
565//! #     gpio::Pins,
566//! #     pac::Peripherals,
567//! #     time::U32Ext,
568//! # };
569//! # let mut pac = Peripherals::take().unwrap();
570//! # let (buses, clocks, tokens) = clock_system_at_reset(
571//! #     pac.OSCCTRL,
572//! #     pac.OSC32KCTRL,
573//! #     pac.GCLK,
574//! #     pac.MCLK,
575//! #     &mut pac.NVMCTRL,
576//! # );
577//! # let pins = Pins::new(pac.PORT);
578//! # let xosc0 = Xosc::from_crystal(
579//! #     tokens.xosc0,
580//! #     pins.pa14,
581//! #     pins.pa15,
582//! #     8.mhz(),
583//! # ).enable();
584//! # let (dpll0, xosc0) = Dpll::from_xosc(tokens.dpll0, xosc0);
585//! # let dpll0 = dpll0.prediv(4).loop_div(50, 0).enable();
586//! # let (gclk0, dfll, dpll0) = clocks.gclk0.swap_sources(clocks.dfll, dpll0);
587//! let dfll_token = dfll.disable().free();
588//! ```
589//!
590//! Our clock tree now looks like this:
591//!
592//! ```text
593//! XOSC0 (8 MHz)
594//! └── DPLL0 (100 MHz)
595//!     └── GCLK0 (100 MHz)
596//!         └── Main clock (100 MHz)
597//! ```
598//!
599//! We have the clocks set up, but we're not using them for anything other than
600//! the main clock. Our final steps will create SERCOM APB and peripheral
601//! clocks and will output the raw GCLK0 to a GPIO pin.
602//!
603//! To enable the APB clock for SERCOM0, we must access the [`Apb`] bus struct.
604//! We provide an [`ApbToken`] to the [`Apb::enable`] method and receive an
605//! [`ApbClk`] in return. APB clocks are [1:1 clocks](self#clock-relationships),
606//! so the `ApbClk` is not wrapped with [`Enabled`].
607//!
608//! ```no_run
609//! # use atsamd_hal::{
610//! #     clock::v2::{
611//! #         clock_system_at_reset,
612//! #         dpll::Dpll,
613//! #         xosc::Xosc,
614//! #     },
615//! #     gpio::Pins,
616//! #     pac::Peripherals,
617//! #     time::U32Ext,
618//! # };
619//! # let mut pac = Peripherals::take().unwrap();
620//! # let (mut buses, clocks, tokens) = clock_system_at_reset(
621//! #     pac.OSCCTRL,
622//! #     pac.OSC32KCTRL,
623//! #     pac.GCLK,
624//! #     pac.MCLK,
625//! #     &mut pac.NVMCTRL,
626//! # );
627//! # let pins = Pins::new(pac.PORT);
628//! # let xosc0 = Xosc::from_crystal(
629//! #     tokens.xosc0,
630//! #     pins.pa14,
631//! #     pins.pa15,
632//! #     8.mhz(),
633//! # ).enable();
634//! # let (dpll0, xosc0) = Dpll::from_xosc(tokens.dpll0, xosc0);
635//! # let dpll0 = dpll0.prediv(4).loop_div(50, 0).enable();
636//! # let (gclk0, dfll, dpll0) = clocks.gclk0.swap_sources(clocks.dfll, dpll0);
637//! # let dfll_token = dfll.disable().free();
638//! let apb_sercom0 = buses.apb.enable(tokens.apbs.sercom0);
639//! ```
640//!
641//! To enable a peripheral channel clock for SERCOM0, we must provide the
642//! corresponding [`PclkToken`], as well as the instance of [`EnabledGclk0`], so
643//! that its counter can be incremented. The resulting clock has the type
644//! `Pclk<Sercom0, Gclk0Id>`.
645//!
646//! ```no_run
647//! # use atsamd_hal::{
648//! #     clock::v2::{
649//! #         clock_system_at_reset,
650//! #         dpll::Dpll,
651//! #         pclk::Pclk,
652//! #         xosc::Xosc,
653//! #     },
654//! #     gpio::Pins,
655//! #     pac::Peripherals,
656//! #     time::U32Ext,
657//! # };
658//! # let mut pac = Peripherals::take().unwrap();
659//! # let (mut buses, clocks, tokens) = clock_system_at_reset(
660//! #     pac.OSCCTRL,
661//! #     pac.OSC32KCTRL,
662//! #     pac.GCLK,
663//! #     pac.MCLK,
664//! #     &mut pac.NVMCTRL,
665//! # );
666//! # let pins = Pins::new(pac.PORT);
667//! # let xosc0 = Xosc::from_crystal(
668//! #     tokens.xosc0,
669//! #     pins.pa14,
670//! #     pins.pa15,
671//! #     8.mhz(),
672//! # ).enable();
673//! # let (dpll0, xosc0) = Dpll::from_xosc(tokens.dpll0, xosc0);
674//! # let dpll0 = dpll0.prediv(4).loop_div(50, 0).enable();
675//! # let (gclk0, dfll, dpll0) = clocks.gclk0.swap_sources(clocks.dfll, dpll0);
676//! # let dfll_token = dfll.disable().free();
677//! # let apb_sercom0 = buses.apb.enable(tokens.apbs.sercom0);
678//! let (pclk_sercom0, gclk0) = Pclk::enable(tokens.pclks.sercom0, gclk0);
679//! ```
680//!
681//! Like [`Dpll<D, I>`], [`Pclk<P, I>`] also takes two type parameters. The
682//! first represents the corresponding peripheral, while the second is again an
683//! [`Id` type](self#id-types) representing the [`Source`] driving the [`Pclk`],
684//! which is restricted by the [`PclkSourceId`] trait. Because peripheral
685//! channel clocks can only be driven by GCLKs, [`PclkSourceId`] is effectively
686//! synonymous with the [`GclkId`] trait.
687//!
688//! Finally, we would like to output GCLK0 to a GPIO pin. Doing so takes a
689//! slightly different approach. This time, we provide a GPIO [`Pin`] to the
690//! [`Gclk`], which creates a [`GclkOut`] and [`Increment`]s the consumer count
691//! for [`EnabledGclk0`].
692//!
693//! ```no_run
694//! # use atsamd_hal::{
695//! #     clock::v2::{
696//! #         clock_system_at_reset,
697//! #         dpll::Dpll,
698//! #         pclk::Pclk,
699//! #         xosc::Xosc,
700//! #     },
701//! #     gpio::Pins,
702//! #     pac::Peripherals,
703//! #     time::U32Ext,
704//! # };
705//! # let mut pac = Peripherals::take().unwrap();
706//! # let (mut buses, clocks, tokens) = clock_system_at_reset(
707//! #     pac.OSCCTRL,
708//! #     pac.OSC32KCTRL,
709//! #     pac.GCLK,
710//! #     pac.MCLK,
711//! #     &mut pac.NVMCTRL,
712//! # );
713//! # let pins = Pins::new(pac.PORT);
714//! # let xosc0 = Xosc::from_crystal(
715//! #     tokens.xosc0,
716//! #     pins.pa14,
717//! #     pins.pa15,
718//! #     8.mhz(),
719//! # ).enable();
720//! # let (dpll0, xosc0) = Dpll::from_xosc(tokens.dpll0, xosc0);
721//! # let dpll0 = dpll0.prediv(4).loop_div(50, 0).enable();
722//! # let (gclk0, dfll, dpll0) = clocks.gclk0.swap_sources(clocks.dfll, dpll0);
723//! # let dfll_token = dfll.disable().free();
724//! # let apb_sercom0 = buses.apb.enable(tokens.apbs.sercom0);
725//! # let (pclk_sercom0, gclk0) = Pclk::enable(tokens.pclks.sercom0, gclk0);
726//! let (gclk0, gclk0_out) = gclk0.enable_gclk_out(pins.pb14);
727//! ```
728//!
729//! We have arrived at our final, desired clock tree. Putting the whole example
730//! together, we get
731//!
732//! ```no_run
733//! use atsamd_hal::{
734//!     clock::v2::{
735//!         clock_system_at_reset,
736//!         dpll::Dpll,
737//!         pclk::Pclk,
738//!         xosc::Xosc,
739//!     },
740//!     gpio::Pins,
741//!     pac::Peripherals,
742//!     time::U32Ext,
743//! };
744//!
745//! let mut pac = Peripherals::take().unwrap();
746//! let (mut buses, clocks, tokens) = clock_system_at_reset(
747//!     pac.OSCCTRL,
748//!     pac.OSC32KCTRL,
749//!     pac.GCLK,
750//!     pac.MCLK,
751//!     &mut pac.NVMCTRL,
752//! );
753//! let pins = Pins::new(pac.PORT);
754//! let xosc0 = Xosc::from_crystal(
755//!     tokens.xosc0,
756//!     pins.pa14,
757//!     pins.pa15,
758//!     8.mhz(),
759//! )
760//! .enable();
761//! let (dpll0, xosc0) = Dpll::from_xosc(tokens.dpll0, xosc0);
762//! let dpll0 = dpll0.prediv(4).loop_div(50, 0).enable();
763//! let (gclk0, dfll, dpll0) = clocks.gclk0.swap_sources(clocks.dfll, dpll0);
764//! let dfll_token = dfll.disable().free();
765//! let apb_sercom0 = buses.apb.enable(tokens.apbs.sercom0);
766//! let (pclk_sercom0, gclk0) = Pclk::enable(tokens.pclks.sercom0, gclk0);
767//! let (gclk0, gclk0_out) = gclk0.enable_gclk_out(pins.pb14);
768//! ```
769//!
770//! [PAC]: crate::pac
771//! [`OSCCTRL`]: crate::pac::Oscctrl
772//! [`OSC32KCTRL`]: crate::pac::Osc32kctrl
773//! [`GCLK`]: crate::pac::Gclk
774//! [`MCLK`]: crate::pac::Mclk
775//! [`Peripherals::steal`]: crate::pac::Peripherals::steal
776//!
777//! [`Ahb`]: ahb::Ahb
778//! [`AhbClk`]: ahb::AhbClk
779//! [`AhbClk<A>`]: ahb::AhbClk
780//! [`AhbClks`]: ahb::AhbClks
781//!
782//! [`Apb`]: apb::Apb
783//! [`Apb::enable`]: apb::Apb::enable
784//! [`ApbClk`]: apb::ApbClk
785//! [`ApbClk<A>`]: apb::ApbClk
786//! [`ApbClks`]: apb::ApbClks
787//! [`ApbToken`]: apb::ApbToken
788//!
789//! [`Dfll`]: dfll::Dfll
790//! [`Dfll<M>`]: dfll::Dfll
791//! [`DfllId`]: dfll::DfllId
792//! [`DfllToken`]: dfll::DfllToken
793//! [`EnabledDfll`]: dfll::EnabledDfll
794//!
795//! [`Dpll`]: dpll::Dpll
796//! [`Dpll<D, I>`]: dpll::Dpll
797//! [`Dpll0`]: dpll::Dpll0
798//! [`Dpll1`]: dpll::Dpll1
799//! [`Dpll0Id`]: dpll::Dpll0Id
800//! [`Dpll1Id`]: dpll::Dpll1Id
801//! [`DpllSourceId`]: dpll::DpllSourceId
802//! [`DpllToken`]: dpll::DpllToken
803//! [`EnabledDpll0`]: dpll::EnabledDpll0
804//!
805//! [`Gclk0`]: gclk::Gclk0
806//! [`GclkId`]: gclk::GclkId
807//! [`EnabledGclk0`]: gclk::EnabledGclk0
808//! [`swap_sources`]: gclk::EnabledGclk0::swap_sources
809//! [`GclkOut`]: gclk::GclkOut
810//!
811//! [`OscUlp32kBase`]: osculp32k::OscUlp32kBase
812//! [`OscUlp1k`]: osculp32k::OscUlp1k
813//! [`OscUlp32k`]: osculp32k::OscUlp32k
814//!
815//! [`Pclk`]: pclk::Pclk
816//! [`Pclk<P, I>`]: pclk::Pclk
817//! [`Pclk::enable`]: pclk::Pclk::enable
818//! [`Pclk::disable`]: pclk::Pclk::disable
819//! [`PclkSourceId`]: pclk::PclkSourceId
820//! [`PclkToken`]: pclk::PclkToken
821//!
822//! [`RtcOsc`]: rtcosc::RtcOsc
823//!
824//! [`Xosc`]: xosc::Xosc
825//! [`Xosc::from_crystal`]: xosc::Xosc::from_crystal
826//! [`Xosc::enable`]: xosc::Xosc::enable
827//! [`Xosc0`]: xosc::Xosc0
828//! [`Xosc0<M>`]: xosc::Xosc0
829//! [`Xosc0Id`]: xosc::Xosc0Id
830//! [`Xosc1Id`]: xosc::Xosc1Id
831//! [`XoscToken`]: xosc::XoscToken
832//! [`EnabledXosc0`]: xosc::EnabledXosc0
833//! [`EnabledXosc0<M, N>`]: xosc::EnabledXosc0
834//! [`CrystalMode`]: xosc::CrystalMode
835//! [`ClockMode`]: xosc::ClockMode
836//!
837//! [`Xosc32kId`]: xosc32k::Xosc32kId
838//!
839//! [type-level]: crate::typelevel
840//! [`Increment`]: crate::typelevel::Increment
841//! [`Decrement`]: crate::typelevel::Decrement
842//!
843//! [`Id`]: Source::Id
844//!
845//! [`gpio::Pins`]: crate::gpio::Pins
846//! [`Pin`]: crate::gpio::Pin
847//!
848//! [`U1`]: typenum::U1
849//! [`Add1`]: typenum::Add1
850//! [`Sub1`]: typenum::Sub1
851//! [`Unsigned`]: typenum::Unsigned
852//!
853//! [interior mutability]: https://doc.rust-lang.org/reference/interior-mutability.html
854
855#![allow(clippy::manual_range_contains)]
856
857use typenum::U0;
858
859use crate::time::Hertz;
860use crate::typelevel::{PrivateDecrement, PrivateIncrement, Sealed};
861
862pub mod ahb;
863pub mod apb;
864pub mod dfll;
865pub mod dpll;
866pub mod gclk;
867pub mod osculp32k;
868pub mod pclk;
869pub mod rtcosc;
870pub mod types;
871pub mod xosc;
872pub mod xosc32k;
873
874mod reset;
875pub use reset::*;
876
877// `Token` types and memory safety
878//
879// Each of the PAC [`Peripherals`] is a zero-sized, singleton struct that
880// mediates access to the MMIO hardware registers. It is not possible to create
881// two instances of any peripheral without causing a run-time panic. These
882// structs implement [`Deref`] by conjuring a pointer to the corresponding
883// register block, and each register within the block is represented by a
884// `vcell::VolatileCell`. Because each register is wrapped in a `VolatileCell`,
885// it is safe to both read and write them through shared references. However,
886// because a read/modify/write operation is not atomic, the [`Peripherals`]
887// structs do not implement [`Sync`].
888//
889// This is a reasonable approach for the PAC, since it is generated from an
890// SVD file. However, it is not the ideal structure for our HAL API. In
891// particular, each [`Peripherals`] struct represents an entire peripheral,
892// rather than a particular functional unit. In the HAL, we want our API to
893// focus on functional units, so we need to define our own abstraction for
894// registers, which will involve `unsafe` code.
895//
896// In the `clock` module, we represent each functional unit with a
897// corresponding `Token` type. Just like the [`Peripherals`], each `Token` type
898// is meant to be a singleton. However, unlike the PAC, we do not have to
899// allow users to create `Token`s directly. Instead, we can have users exchange
900// [`Peripherals`] for the `Token`s. Because each PAC struct is a singleton, we
901// can guarantee each `Token` will be a singleton as well. With this approach,
902// we don't need to implement our own run-time panicking; we simply extend the
903// existing guarantees of the PAC.
904//
905// To implement a memory safe API, we must ensure that all `Token` types access
906// mutually exclusive sets of registers. In that way, we guarantee no two
907// `Token` types can access the same register. Moreover, in contrast to the PAC
908// [`Peripherals`], we can make our `Token`s [`Sync`] if we remove all interior
909// mutability and guarantee that writing or modifying a register requires
910// ownership or an `&mut` reference.
911//
912// Thus, our `Token`-based API should be memory safe if we always obey the
913// following requirements:
914//   - It should be `unsafe` to create a `Token` type unless it is created in
915//     exchange for the corresponding PAC peripheral struct.
916//   - Each `Token` type should have access to a mutually exclusive set of
917//     registers relative to the other `Token`s.
918//   - Writing or modifying a register should always require ownership of, or an
919//     `&mut` reference to, the corresponding `Token`.
920//   - When conjuring references to PAC registers or register blocks, we should
921//     *only* use shared, `&` references. There is no need to use exclusive,
922//     `&mut` references, because each register is wrapped in a `VolatileCell`.
923//     Moreover, using `&mut` references could cause UB, if we accidentally
924//     create two simultaneous references to the same register block from
925//     different `Tokens`.
926//
927// [`Peripherals`]: crate::pac::Peripherals
928// [`Deref`]: core::ops::Deref
929
930/// Marks [`Enabled`] 1:N producer clocks that can act as a clock source
931///
932/// Implementers of this type act as producer clocks and feed consumer clocks in
933/// the clock tree. All implementors are [`Enabled`], 1:N clocks. The `Id`
934/// associated type maps to the corresponding [`Id` type](self#id-types) of the
935/// implementer.
936///
937/// See the documentation on [`Source` clocks](self#acting-as-a-clock-source)
938/// for more details.
939pub trait Source: Sealed {
940    /// Corresponding `Id` type for the implementer
941    ///
942    /// A given implementer of [`Source`] might have type parameters
943    /// representing its configuration. For instance, [`EnabledXosc0<M>`] has a
944    /// type parameter to track its [`Mode`]. However, a consumer clock
945    /// typically does not care about such configuration. It only needs to
946    /// know *which* upstream clock is its [`Source`].
947    ///
948    /// `Id` types exist to fill this role. They represent the *identity* of a
949    /// given clock, regardless of any configuration. This is like the
950    /// distinction between a passport and a person. A passport identifies a
951    /// person, regardless of changes to their clothes or hair.
952    ///
953    /// Thus, [`EnabledXosc0<M>`] implements [`Source`] with `Id = `[`Xosc0Id`],
954    /// regardless of `M`.
955    ///
956    /// See the documentation on [`Id` types](self#id-types) for more details.
957    ///
958    /// [`EnabledXosc0<M>`]: xosc::EnabledXosc0
959    /// [`Mode`]: xosc::Mode
960    /// [`Xosc0Id`]: xosc::Xosc0Id
961    type Id;
962
963    /// Return the frequency of the clock source
964    fn freq(&self) -> Hertz;
965}
966
967/// An enabled, 1:N clock with a compile-time counter for N
968///
969/// This struct is a wrapper around other clock types from this module. It
970/// represents a clock, `T`, that has been enabled, and it maintains a
971/// compile-time counter, `N`, of its consumer clocks in the clock tree.
972///
973/// Compile-time counting allows the API to restrict when clocks may be modified
974/// or disabled. For example, `Enabled` clocks can only be disabled when their
975/// counter is [`U0`].
976///
977/// The type-level counter is implemented using [`Unsigned`] integers from
978/// the [`typenum`] crate, and it is modified using the [`Increment`] and
979/// [`Decrement`] traits.
980///
981/// See the [`Enabled` wrapper documentation](self#the-enabled-wrapper) for more
982/// details.
983///
984/// [`EnabledGclk0`]: gclk::EnabledGclk0
985/// [`Increment`]: crate::typelevel::Increment
986/// [`Decrement`]: crate::typelevel::Decrement
987/// [`Unsigned`]: typenum::Unsigned
988pub struct Enabled<T, N = U0>(pub(crate) T, N);
989
990impl<T, N> Sealed for Enabled<T, N> {}
991
992impl<T, N: Default> Enabled<T, N> {
993    #[inline]
994    pub(crate) fn new(t: T) -> Self {
995        Enabled(t, N::default())
996    }
997}
998
999impl<T, N: PrivateIncrement> PrivateIncrement for Enabled<T, N> {
1000    type Inc = Enabled<T, N::Inc>;
1001
1002    #[inline]
1003    fn inc(self) -> Self::Inc {
1004        Enabled(self.0, self.1.inc())
1005    }
1006}
1007
1008impl<T, N: PrivateDecrement> PrivateDecrement for Enabled<T, N> {
1009    type Dec = Enabled<T, N::Dec>;
1010
1011    #[inline]
1012    fn dec(self) -> Self::Dec {
1013        Enabled(self.0, self.1.dec())
1014    }
1015}