Mynd:Winter-NAO-Index.svg

Page contents not supported in other languages.
Úr Wikipediu, frjálsa alfræðiritinu

Upphafleg skrá(SVG-skrá, að nafni til 566 × 351 mynddílar, skráarstærð: 154 KB)

Skrá þessi er af Wikimedia Commons, og deilt meðal annarra verkefna og nýtist því þar. Hér fyrir neðan er afrit af skráarsíðunni þar.

Lýsing

Lýsing
English: Winter (December through March) index of the North Atlantic oscillation (NAO) based on the difference of normalized sea level pressure (SLP) between Gibraltar and SW Iceland since 1823, with loess smoothing (black, confidence interval in grey).
Dagsetning
Uppruni

Data source : Climatic Research Unit, University of East Anglia.

Reference : Jones, P.D., Jónsson, T. and Wheeler, D., 1997: Extension to the North Atlantic Oscillation using early instrumental pressure observations from Gibraltar and South-West Iceland. Int. J. Climatol. 17, 1433-1450. doi: 10.1002/(SICI)1097-0088(19971115)17:13<1433::AID-JOC203>3.0.CO;2-P
Höfundarréttarhafi

Oeneis. Originally created by Marsupilami ;

updated with 2021 data and produced with R code by Oeneis
Aðrar útgáfur

[breyta]

Create this graph

Annual and winter NAO in multiple languages

 
This chart was created with R.

R code

# Build multi languages plots for annual and winter NAO
# based on CRU data.
# 
# Used for https://commons.wikimedia.org/wiki/Template:Other_versions/NAO_winter
# e.g. https://commons.wikimedia.org/wiki/File:Winter-NAO-Index.svg
# See https://commons.wikimedia.org/wiki/Template:Other_versions/NAO_winter.R to edit this file

library(dplyr)
library(readr)
library(tidyr)
library(ggplot2)
library(stringr)
library(glue)

theme_set(theme_bw())
theme_update(plot.caption = element_text(size = 7))
oldDec <- getOption("OutDec")

# get data : winter and annual
# add sign column for colors
nao_cru <- "https://crudata.uea.ac.uk/cru/data/nao/nao.dat" %>% 
  read_table(col_types = "iddddddddddddd", na = "-99.99", col_names = c("year", 1:12, "annual")) %>% 
  pivot_longer(-1, names_to = "period", values_to = "nao")

nao_cru_djfm <- nao_cru %>% 
  filter(period %in% c("12", "1", "2", "3")) %>%
  mutate(winter = if_else(period == "12", 
                          paste(year, year + 1, sep = "-"),
                          paste(year - 1, year, sep = "-"))) %>% 
  group_by(winter) %>% 
  summarise(nao = mean(nao, na.rm = TRUE)) %>% 
  mutate(year = as.numeric(str_extract(winter, "^\\d{4}")),
         sign = if_else(nao < 0, "negative", "positive")) %>% 
  filter(year > 1822)

nao_cru_annual <- nao_cru %>% 
  filter(period == "annual") %>% 
  mutate(sign = if_else(nao < 0, "negative", "positive")) %>% 
  filter(year > 1822)


# manage languages
language <- list(
  es_ES = list(
    winter = list(
      data = nao_cru_djfm,            
      title = "Índice de invierno de la Oscilación del Atlántico Norte (NAO)",
      subtitle = "Gibraltar - SW de Islandia, de diciembre a marzo",
      caption = "https://w.wiki/4b$m\nData : Climatic Research Unit, University of East Anglia.\nJones, P.D., Jónsson, T. y Wheeler, D. (1997)\nActualizado regularmente. Accedido a",
      x = "Año",
      y = "Diferencia de presión normalizada a nivel del mar (hPa)",
      outDec = "."
    ),
    annual = list(
      data = nao_cru_annual,
      title = "Índice anual de la Oscilación del Atlántico Norte (NAO)",
      subtitle = "Gibraltar - SW de Islandia",
      caption = "Data : Climatic Research Unit, University of East Anglia.\nJones, P.D., Jónsson, T. y Wheeler, D. (1997)\nActualizado regularmente. Accedido a",
      x = "Año",
      y = "Diferencia de presión normalizada a nivel del mar (hPa)",
      outDec = "."
    )
  ),
  de_DE = list(
    winter = list(
      data = nao_cru_djfm,
      title = "Nordatlantischen Oszillation (NAO) Winter Index",
      subtitle = "Gibraltar - SW Island, Dezember bis März",
      caption = "https://w.wiki/4b$m\nDatei : Climatic Research Unit, University of East Anglia.\nJones, P.D., Jónsson, T. und Wheeler, D. (1997)\nRegelmäßig aktualisiert. Zugänglich am",
      x = "Jahre",
      y = "Differenz der standardisierten Luftdruck (hPa)",
      outDec = ","
    ),
    annual = list(
      data = nao_cru_annual,      
      title = "Nordatlantischen Oszillation (NAO) Index",
      subtitle = "Gibraltar - SW Island",
      caption = "Datei : Climatic Research Unit, University of East Anglia.\nJones, P.D., Jónsson, T. und Wheeler, D. (1997)\nRegelmäßig aktualisiert. Zugänglich am",
      x = "Jahre",
      y = "Differenz der standardisierten Luftdruck (hPa)",
      outDec = ","
    )
  ),
  en_US = list(
    winter = list(
      data = nao_cru_djfm,            
      title = "North Atlantic Oscillation (NAO) winter index",
      subtitle = "Gibraltar - SW Iceland, December to March",
      caption = "https://w.wiki/4b$m\nData : Climatic Research Unit, University of East Anglia.\nJones, P.D., Jónsson, T. and Wheeler, D. (1997)\nUpdated regularly. Accessed",
      x = "Year",
      y = "Difference of normalized sea level pressure (hPa)",
      outDec = "."
    ),
    annual = list(
      data = nao_cru_annual,
      title = "North Atlantic Oscillation (NAO) annual index",
      subtitle = "Gibraltar - SW Iceland",
      caption = "Data : Climatic Research Unit, University of East Anglia.\nJones, P.D., Jónsson, T. and Wheeler, D. (1997)\nUpdated regularly. Accessed",
      x = "Year",
      y = "Difference of normalized sea level pressure (hPa)",
      outDec = "."
    )
  ),
  fr_FR = list(
    winter = list(
      data = nao_cru_djfm,
      title = "Indice hivernal de l'oscillation nord-atlantique (ONA)",
      subtitle = "Gibraltar - SW Islande, décembre à mars",
      caption = "https://w.wiki/4b$m\nDonnées : Climatic Research Unit, University of East Anglia.\nJones, P.D., Jónsson, T. et Wheeler, D. (1997)\nMise à jour régulière. Accédé le",
      x = "année",
      y = "différence de pression normalisée (hPa)",
      outDec = ","
    ),
    annual = list(
      data = nao_cru_annual,
      title = "Indice annuel de l'oscillation nord-atlantique (ONA)",
      subtitle = "Gibraltar - SW Islande",
      caption = "Données : Climatic Research Unit, University of East Anglia.\nJones, P.D., Jónsson, T. et Wheeler, D. (1997)\nMise à jour régulière. Accédé le",
      x = "année",
      y = "différence de pression normalisée (hPa)",
      outDec = ","
    )
  ),
  it_IT = list(
    winter = list(
      data = nao_cru_djfm,
      title = "Indice invernale dell'Oscillazione Nord Atlantica (NAO)",
      subtitle = "Gibilterra - SW Islanda, da dicembre a marzo",
      caption = "https://w.wiki/4b$m\nDati : Climatic Research Unit, University of East Anglia.\nJones, P.D., Jónsson, T. e Wheeler, D. (1997)\nAggiornato regolarmente. Accesso a",
      x = "Anno",
      y = "Differenza di pressione normalizzata\nal livello del mare (hPa)",
      outDec = ","
    ),
    annual = list(
      data = nao_cru_annual,
      title = "Indice annuale dell'Oscillazione Nord Atlantica (NAO)",
      subtitle = "Gibilterra - SW Islanda",
      caption = "Dati : Climatic Research Unit, University of East Anglia.\nJones, P.D., Jónsson, T. e Wheeler, D. (1997)\nAggiornato regolarmente. Accesso a",
      x = "Anno",
      y = "Differenza di pressione normalizzata\nal livello del mare (hPa)",
      outDec = ","
    )
  )
)


for (l in names(language)) {
  message(l)
  
  for (t in names(language[[l]])) {
    message(t)
    current <- language[[l]][[t]]
    options(OutDec = current$outDec)
    
    # plot graph
    ggplot(current$data, aes(year, nao)) +
      geom_col(aes(fill = sign)) +
      geom_smooth(span = .1, color = "black", alpha = 0.3) +
      scale_fill_manual(values = c("positive" = "darkorange2",
                                   "negative" = "deepskyblue3")) +
      scale_x_continuous(breaks = seq(1820, max(current$data$year), 20)) +
      guides(fill = "none") +
      labs(title = current$title,
           subtitle = current$subtitle,
           caption = glue("{current$caption} {format(Sys.Date(), '%Y-%m-%d')}"),
           x = current$x,
           y = current$y)
    
    ggsave(file = glue("nao_cru_{t}_{l}_{Sys.Date()}.svg"), 
           width = 20,
           height = 12.4,
           units = "cm",
           scale = 0.8,
           device = svg)
  }
}

options(OutDec = oldDec)



Leyfisupplýsingar:

Public domain I, the copyright holder of this work, release this work into the public domain. This applies worldwide.
In some countries this may not be legally possible; if so:
I grant anyone the right to use this work for any purpose, without any conditions, unless such conditions are required by law.

Captions

Add a one-line explanation of what this file represents
Winter index of the North Atlantic oscillation

Items portrayed in this file

depicts enska

28. september 2017

MIME type enska

image/svg+xml

Breytingaskrá skjals

Smelltu á dagsetningu eða tímasetningu til að sjá hvernig hún leit þá út.

(nýjustu | elstu) Skoða (nýrri 10 | ) (10 | 20 | 50 | 100 | 250 | 500).
Dagsetning/TímiSmámyndVíddirNotandiAthugasemd
núverandi22. nóvember 2023 kl. 22:44Smámynd útgáfunnar frá 22. nóvember 2023, kl. 22:44566 × 351 (154 KB)Oeneisupdate 2022-2023
22. desember 2022 kl. 17:02Smámynd útgáfunnar frá 22. desember 2022, kl. 17:02566 × 351 (153 KB)Oeneis2022 update
15. ágúst 2022 kl. 08:14Smámynd útgáfunnar frá 15. ágúst 2022, kl. 08:14566 × 351 (154 KB)Oeneisupdate with 2021-2022 data
26. desember 2021 kl. 17:16Smámynd útgáfunnar frá 26. desember 2021, kl. 17:16566 × 351 (150 KB)Oeneisupdate wiki link
26. desember 2021 kl. 12:03Smámynd útgáfunnar frá 26. desember 2021, kl. 12:03566 × 351 (149 KB)Oeneis2020-2021 data. Using CRU data
1. nóvember 2020 kl. 13:25Smámynd útgáfunnar frá 1. nóvember 2020, kl. 13:25566 × 351 (137 KB)Oeneis2019 data
21. október 2018 kl. 08:22Smámynd útgáfunnar frá 21. október 2018, kl. 08:22566 × 351 (135 KB)Oeneis2017-2018 data
8. október 2017 kl. 14:49Smámynd útgáfunnar frá 8. október 2017, kl. 14:49566 × 351 (138 KB)Oeneisuse device = svg to get a nicer renderer
28. september 2017 kl. 20:14Smámynd útgáfunnar frá 28. september 2017, kl. 20:14512 × 317 (46 KB)Oeneis2016-2017 data
16. nóvember 2016 kl. 15:57Smámynd útgáfunnar frá 16. nóvember 2016, kl. 15:57512 × 317 (46 KB)Oeneis2016 data
(nýjustu | elstu) Skoða (nýrri 10 | ) (10 | 20 | 50 | 100 | 250 | 500).

Eftirfarandi síða notar þessa skrá:

Altæk notkun skráar

Eftirfarandi wikar nota einnig þessa skrá:

Lýsigögn