File:Winter-NAO-Index.svg

维基共享资源,媒体文件资料库
跳转到导航 跳转到搜索

原始文件(SVG文件,尺寸为566 × 351像素,文件大小:154 KB)

说明

说明

添加一行文字以描述该文件所表现的内容
Winter index of the North Atlantic oscillation

摘要[编辑]

描述
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).
日期
来源

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
作者

Oeneis. Originally created by Marsupilami ;

updated with 2021 data and produced with R code by Oeneis
其他版本

[编辑]

Create this graph[编辑]

Annual and winter NAO in multiple languages

 
矢量图使用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)



许可协议[编辑]

Public domain 我,本作品著作权人,释出本作品至公有领域。这适用于全世界。
在一些国家这可能不合法;如果是这样的话,那么:
我无条件地授予任何人以任何目的使用本作品的权利,除非这些条件是法律规定所必需的。

文件历史

点击某个日期/时间查看对应时刻的文件。

最新 | 最旧) 查看(较新10条 | )(10 | 20 | 50 | 100 | 250 | 500
日期/时间缩⁠略⁠图大小用户备注
当前2023年11月22日 (三) 22:442023年11月22日 (三) 22:44版本的缩略图566 × 351(154 KB)Oeneis留言 | 贡献update 2022-2023
2022年12月22日 (四) 17:022022年12月22日 (四) 17:02版本的缩略图566 × 351(153 KB)Oeneis留言 | 贡献2022 update
2022年8月15日 (一) 08:142022年8月15日 (一) 08:14版本的缩略图566 × 351(154 KB)Oeneis留言 | 贡献update with 2021-2022 data
2021年12月26日 (日) 17:162021年12月26日 (日) 17:16版本的缩略图566 × 351(150 KB)Oeneis留言 | 贡献update wiki link
2021年12月26日 (日) 12:032021年12月26日 (日) 12:03版本的缩略图566 × 351(149 KB)Oeneis留言 | 贡献2020-2021 data. Using CRU data
2020年11月1日 (日) 13:252020年11月1日 (日) 13:25版本的缩略图566 × 351(137 KB)Oeneis留言 | 贡献2019 data
2018年10月21日 (日) 08:222018年10月21日 (日) 08:22版本的缩略图566 × 351(135 KB)Oeneis留言 | 贡献2017-2018 data
2017年10月8日 (日) 14:492017年10月8日 (日) 14:49版本的缩略图566 × 351(138 KB)Oeneis留言 | 贡献use device = svg to get a nicer renderer
2017年9月28日 (四) 20:142017年9月28日 (四) 20:14版本的缩略图512 × 317(46 KB)Oeneis留言 | 贡献2016-2017 data
2016年11月16日 (三) 15:572016年11月16日 (三) 15:57版本的缩略图512 × 317(46 KB)Oeneis留言 | 贡献2016 data
最新 | 最旧) 查看(较新10条 | )(10 | 20 | 50 | 100 | 250 | 500

全域文件用途

以下其他wiki使用此文件:

元数据