PRO vu_movie, ut, map_type          , $
        ut_extra        = ut_extra      , $
        path            = path          , $
        filter          = filter        , $
        highmark        = highmark      , $
        movie_destination=movie_destination,$
        image_destination=image_destination,$
        hdr             = hdr           , $
        ff              = ff            , $
        movie_file      = movie_file    , $
        delay           = delay         , $
        png             = png           , $
        gif             = gif           , $
        mpeg            = mpeg          , $
        fillsky         = fillsky       , $
        skip            = skip          , $
        type            = type          , $
        roi_offset      = roi_offset    , $
        ut_off          = ut_off        , $
        silent          = silent        , $
        nv_filter       = nv_filter     , $
        nv_hdr          = nv_hdr        , $
        nv_ff           = nv_ff         , $
        source          = source        , $
        _extra          = _extra
    @compile_opt.pro        ; On error, return to caller

InitVar, silent  , 0

InitVar, fillsky , /key
InitVar, map_type, 'synoptic'
InitVar, path    , filepath(root=getenv('NAGOYA'), subdir='slow','final')
InitVar, ut_off  , 0.0

InitVar, mpeg    , /key
InitVar, png     , /key
InitVar, gif     , /key

png OR= 1-gif and 1-mpeg

fillsky AND= map_type EQ 'earth_skysweep'
uday = TimeUnit(/day)

case IsType(movie_destination, /defined) of
0: movie_destination = getenv('TUB')
1: begin

    ; Make sure the destination dir for the movies exists. If not use $TUB.

    IF NOT CheckDir(movie_destination) THEN BEGIN
        say, threshold=2, silent=silent, $
            'movie directory '+movie_destination+' does not exist; using '+getenv('TUB')+' instead'
        movie_destination = getenv('TUB')
    ENDIF

END
ENDCASE

; If an explicit destination for the individual frames is specified
; check whether it exists. If not then ignore it.

keep_frms = IsType(image_destination, /defined)
IF keep_frms THEN keep_frms = CheckDir(image_destination)

IF NOT keep_frms THEN image_destination = getenv('TUB')

CASE map_type OF
'synoptic'          : type = vu_type_insitu(map_type, _extra=_extra, type=type)
'earth_skysnap'     : type = vu_type_skymap(map_type, _extra=_extra, type=type)
'earth_skysweep'    : type = vu_type_skymap(map_type, _extra=_extra, type=type)
'earth_insitu'      : type = vu_type_insitu(map_type, _extra=_extra, type=type)
'earth_remoteview'  : type = vu_type_insitu(map_type, _extra=_extra, type=type)
'earth_solardisk'   : type = vu_type_insitu(map_type, _extra=_extra, type=type)
'planarcut'         : type = vu_type_insitu(map_type, _extra=_extra, type=type)
'mercury_insitu'    : type = vu_type_insitu(map_type, _extra=_extra, type=type)
'venus_insitu'      : type = vu_type_insitu(map_type, _extra=_extra, type=type)
'mars_insitu'       : type = vu_type_insitu(map_type, _extra=_extra, type=type)
'ulysses_insitu'    : type = vu_type_insitu(map_type, _extra=_extra, type=type)
'stereoa_insitu'    : type = vu_type_insitu(map_type, _extra=_extra, type=type)
'stereob_insitu'    : type = vu_type_insitu(map_type, _extra=_extra, type=type)
ENDCASE

IF (where(type.data))[0] EQ -1 THEN BEGIN
    say, threshold=2, silent=silent, ['no movie type selected','... ABORTING']
    RETURN
ENDIF

; A single time is take to be the end of the movie.
; Go back one week.

mov_range = Carrington(ut,/get_time)
IF n_elements(mov_range) EQ 1 THEN  $
    mov_range = TimeOp(/add, mov_range, TimeSet(/diff, day=[-7,0]))

; For skysweeps add another day to the start of the movie. This day is used to
; make sure the first image in the movie has the whole sky filled.

IF fillsky THEN $
    mov_range[0] = TimeOp(/add, mov_range[0], TimeSet(/diff, day=-1))

; If hdr and ff are still available from a previous run, and passed here as
; input arguments then the read section is skipped (saves a lot of time).

cnt = n_elements(hdr)
IF cnt EQ 0 THEN BEGIN

    CASE 1 OF
    IsTime(ut_extra          ): range = TimeOp(/add,mov_range,ut_extra)
    IsType(ut_extra, /defined): range = TimeOp(/add,mov_range,TimeSet(/diff,day=ut_extra))
    ELSE                      : range = mov_range
    ENDCASE

    ; Get a list of all files. Don't read the headers yet. Just extract
    ; the Carrington variables from the file names

    times = vu_select(files, /nohdr, path=path, filter=filter, count=cnt, silent=silent, highmark=highmark)

    ; Determine which files are inside 'mov_range'.

    IF cnt GT 0 THEN BEGIN
        dt = TimeOp(/subtract,mov_range[1],mov_range[0],uday)
        tt = TimeOp(/subtract,times       ,mov_range[0],uday)
        tmp = where(0 le tt and tt le dt, cnt)
        ;tmp = where(0 le TimeOp(/subtract,times,mov_range[0],uday) and TimeOp(/subtract,times,mov_range[1],uday) le 0, cnt)
    ENDIF

    IF cnt EQ 0 THEN BEGIN
        say, threshold=2, silent=silent, ['no files in ['+strjoin(TimeGet(mov_range,/ymd),',')+']','... ABORTING']
        RETURN
    ENDIF

    ; Check for files inside 'range' (may extend beyond 'mov_range'). Read these files.

    dt = TimeOp(/subtract,range[1],range[0],uday)
    tt = TimeOp(/subtract,times   ,range[0],uday)
    tmp = where(0 LE tt AND tt LE dt, cnt)
    ;tmp = where(0 le TimeOp(/subtract,times,range[0],uday) and TimeOp(/subtract,times,range[1],uday) le 0, cnt)
    files = files[tmp]

    IF IsType(skip, /defined) THEN BEGIN
        tmp = where( (indgen(cnt) mod skip) EQ 0, cnt)
        IF cnt NE 0 then files = files[tmp]
    ENDIF

    hdr = vu_select(files, /check, /read, /get_roi, silent=silent+1, ff=ff, roi_offset=roi_offset)

ENDIF

; Collect density data matching the magnetic data stored in hdr and ff
; (used for remoteview only)

IF IsType(nv_hdr, /undefined) AND IsType(nv_filter,/defined) THEN BEGIN

    SetFileSpec, hdr.file
    bb_prefix_len = strlen(hdr[0].prefix)

    nv_prefix_len = strpos(nv_filter,'*.*')
    IF nv_prefix_len EQ -1 THEN nv_prefix_len = strlen(nv_filter)

    nv_files = strmid(nv_filter,0,nv_prefix_len)+strmid(GetFileSpec(from='name'),bb_prefix_len)
    nv_files = filepath(root=(GetFileSpec(upto='directory'))[0], nv_files)

    nv_hdr = vu_select(nv_files, /check, /read, /get_roi, silent=silent+1, ff=nv_ff, roi_offset=roi_offset)

    IF n_elements(nv_hdr) NE cnt THEN BEGIN
        destroyvar, nv_hdr, nv_ff
        say, threshold=2, silent=silent, ['error reading data: '+nv_filter,'... ABORTING']
        RETURN
    ENDIF

    ; hack added by jclover to help with vu_movie call in forecast_movie
    ; this should interpolate the magnetic field data to the same dimensions as
    ; the density/velocity data and allow remoteview to run correctly.

    nvdims = size(nv_ff,/dim)
    bbdims = size(   ff,/dim)
    ;IF map_type EQ 'earth_remoteview' AND nv_hdr[0].prefix EQ 'nv3h' AND hdr[0].prefix EQ 'nson' THEN BEGIN
    n = where(bbdims[0:2] NE nvdims[0:2])
    IF n[0] NE -1 THEN BEGIN

        ; Probably need to do some safety checks.
        ; Is there only one source surface for all nv and bb data?
        ; Is the distance step for all nv arrays the same?
        ; Is the distance step for all bb arrays the same?
        ; Is the longitude range the same (it's not! PPH)

        bblng = (bbdims[0]-1)*gridgen(nvdims[0],/one)
        bblat = (bbdims[1]-1)*gridgen(nvdims[1],/one)
        bbrad = (bbdims[2]-1)*gridgen(nvdims[2],/one)

        hdr.nlng = nv_hdr.nlng
        hdr.nlat = nv_hdr.nlat
        hdr.nrad = nv_hdr.nrad
        hdr.distance_step = nv_hdr.distance_step

        bbdims[n] = nvdims[n]
        ff_bi = fltarr(bbdims)
        FOR i=0,cnt-1 DO            $   ; loop over times, cnt = bbdims[4] = nvdims[4]
            FOR j=0,bbdims[3]-1 DO  $   ; loop over magnetic components
                ff_bi[*,*,*,j,i] = interpolate(ff[*,*,*,j,i],bblng,bblat,bbrad,/grid)
        ff = ff_bi

    ENDIF

ENDIF

time = vu_get(hdr, /uttime)

tmp = where(TimeOp(/subtract,time,mov_range[0],uday) GE 0 AND   $
            TimeOp(/subtract,time,mov_range[1],uday) LE 0, cnt)

IF cnt EQ 0 THEN BEGIN
    say, threshold=2, silent=silent, ['no times left to make movies','... ABORTING']
    RETURN
ENDIF

time = time[tmp]


CASE fillsky OF
0: npad = 0
1: tmp  = where(TimeOp(/subtract,time,time[0],uday) LT 1, npad)
ENDCASE

IF map_type EQ 'earth_skysweep' THEN BEGIN
    band = TimeOp(/subtract,time[1],time[0],TimeUnit(/hour))
    band = round(band)                  ; Time between first two files used
    band = [band, band]                 ; 'band' is only used by vu_localskymap if keyword /track
ENDIF                                   ; .. IS PASSED HERE BY CALLER.

IF png THEN BEGIN
    boost, frm_type, '.png'
    boost, mov_type, '.mng'
ENDIF

IF gif THEN BEGIN
    boost, frm_type, '.gif'
    boost, mov_type, '.gif'
ENDIF

IF mpeg THEN BEGIN
    boost, frm_type, '.gif'
    boost, mov_type, '.mpeg'
ENDIF

nmov = n_elements(mov_type)

; Postfix the individual frames with the time. If only one time is input
; use the file name vu_get(hdr,/file) instead.
; Note that <module> is replaced by the actual module name in vu_get_page

frm_file = TimeGet(time, /string, /_ydoy)
IF n_elements(uniq(frm_file)) EQ 1 THEN $
    frm_file = GetFileSpec(vu_get(hdr, /file), from='name', upto='type')

frm_file = filepath(root=image_destination, '<module>_'+frm_file)

FOR i=0,cnt-1 DO BEGIN                  ; LOOP OVER ALL FILES

    CASE type.display OF
    'synoptic':         $
        vu_synopticmap, hdr, ff,          $
            ut0         = time[i]       , $
            type        = type          , $
            silent      = silent+1      , $
            destination = frm_file[i]   , $
            gif         = gif OR mpeg   , $
            png         = png           , $
            module      = module        , $
            _extra      = _extra        , $

            same_T0     = i NE 0

    'earth_skysnap':    $
        vu_earthskymap, hdr, ff,          $
            ut0         = time[i]       , $
            type        = type          , $
            silent      = silent+1      , $
            destination = frm_file[i]   , $
            gif         = gif OR mpeg   , $
            png         = png           , $
            module      = module        , $
            _extra      = _extra

    'earth_skysweep':   $
        vu_localskymap, hdr, ff,          $
            ut0         = time[i]       , $
            type        = type          , $
            silent      = silent+1      , $
            destination = frm_file[i]   , $
            gif         = gif OR mpeg   , $
            png         = png           , $
            module      = module        , $
            _extra      = _extra        , $

            RA_full     = RA_full       , $
            F_full      = F_full        , $
            band        = band

    'earth_insitu': BEGIN

        InitVar, source, ([Instrument(/aceb),Instrument(/acesw)])[strmid(type.label,0,2) EQ '_v' OR strmid(type.label,0,2) eq '_n']
        vu_insitu, hdr, ff,               $
            ut0         = time[i]       , $
            type        = type          , $
            silent      = silent+1      , $
            destination = frm_file[i]   , $
            gif         = gif OR mpeg   , $
            png         = png           , $
            module      = module        , $
            _extra      = _extra        , $

            same_T0     = i NE 0        , $
            /timeseries                 , $
            thick       = type.thick    , $
            charsize    = type.charsize , $
            source      = source

    END

    'earth_solardisk':  $
        vu_solardisk, hdr, ff,            $
            ut0         = TimeOp(/add,time[i],TimeSet(/diff,day=ut_off)) , $
            type        = type          , $
            silent      = silent+1      , $
            destination = frm_file[i]   , $
            gif         = gif OR mpeg   , $
            png         = png           , $
            module      = module        , $
            _extra      = _extra

    'planarcut':        $
        vu_planarcut, hdr, ff,            $
            ut0         = TimeOp(/add,time[i],TimeSet(/diff,day=ut_off)) , $
            type        = type          , $
            silent      = silent+1      , $
            destination = frm_file[i]   , $
            gif         = gif OR mpeg   , $
            png         = png           , $
            module      = module        , $
            _extra      = _extra

    'earth_remoteview': BEGIN

        CASE IsType(nv_hdr,/defined) OF
        0: vu_remoteview, hdr, ff,        $
            ut0         = time[i]       , $
            type_ff     = type          , $
            silent      = silent+1      , $
            destination = frm_file[i]   , $
            gif         = gif OR mpeg   , $
            png         = png           , $
            module      = module        , $
            _extra      = _extra        , $

            view_time   = time[i]       , $
            charsize    = type.charsize

        1: vu_remoteview, nv_hdr, nv_ff,  $
            ut0         = time[i]       , $
            type_ff     = type          , $
            silent      = silent+1      , $
            destination = frm_file[i]   , $
            gif         = gif OR mpeg   , $
            png         = png           , $
            module      = module        , $
            _extra      = _extra        , $

            view_time   = time[i]       , $
            charsize    = type.charsize , $
            /meshhcs                    , $
            hdr_bb      = hdr           , $
            bb          = ff

        ENDCASE

    END

    'mercury_insitu':   $
        vu_insitu, hdr, ff,               $
            ut0         = time[i]       , $
            type        = type          , $
            silent      = silent+1      , $
            destination = frm_file[i]   , $
            gif         = gif OR mpeg   , $
            png         = png           , $
            module      = module        , $
            _extra      = _extra        , $

            same_T0     = i NE 0        , $
            /timeseries                 , $
            thick       = type.thick    , $
            charsize    = type.charsize , $
            body        = jpl_body(/mercury,/string)

    'venus_insitu':     $
        vu_insitu, hdr, ff,               $
            ut0         = time[i]       , $
            type        = type          , $
            silent      = silent+1      , $
            destination = frm_file[i]   , $
            gif         = gif OR mpeg   , $
            png         = png           , $
            module      = module        , $
            _extra      = _extra        , $

            same_T0     = i NE 0        , $
            /timeseries                 , $
            thick       = type.thick    , $
            charsize    = type.charsize , $
            body        = jpl_body(/venus,/string)

    'mars_insitu':      $
        vu_insitu, hdr, ff,               $
            ut0         = time[i]       , $
            type        = type          , $
            silent      = silent+1      , $
            destination = frm_file[i]   , $
            gif         = gif OR mpeg   , $
            png         = png           , $
            module      = module        , $
            _extra      = _extra        , $

            same_T0     = i NE 0        , $
            /timeseries                 , $
            thick       = type.thick    , $
            charsize    = type.charsize , $
            body        = jpl_body(/mars,/string)

    'ulysses_insitu':   $
        vu_insitu, hdr, ff,               $
            ut0         = time[i]       , $
            type        = type          , $
            silent      = silent+1      , $
            destination = frm_file[i]   , $
            gif         = gif OR mpeg   , $
            png         = png           , $
            module      = module        , $
            _extra      = _extra        , $

            same_T0     = i NE 0        , $
            /timeseries                 , $
            thick       = type.thick    , $
            charsize    = type.charsize , $
            body        = big_body('Ulysses')

    'stereoa_insitu':   $
        vu_insitu, hdr, ff,               $
            ut0         = time[i]       , $
            type        = type          , $
            silent      = silent+1      , $
            destination = frm_file[i]   , $
            gif         = gif OR mpeg   , $
            png         = png           , $
            module      = module        , $
            _extra      = _extra        , $

            same_T0     = i NE 0        , $
            /timeseries                 , $
            thick       = type.thick    , $
            charsize    = type.charsize , $
            body        = big_body('Stereo A')

    'stereob_insitu':   $
        vu_insitu, hdr, ff,               $
            ut0         = time[i]       , $
            type        = type          , $
            silent      = silent+1      , $
            destination = frm_file[i]   , $
            gif         = gif OR mpeg   , $
            png         = png           , $
            module      = module        , $
            _extra      = _extra        , $

            same_T0     = i NE 0        , $
            /timeseries                 , $
            thick       = type.thick    , $
            charsize    = type.charsize , $
            body        = big_body('Stereo B')

    ENDCASE

ENDFOR

frm_wild   = filepath(root=image_destination, module+'_*')
movie_file = filepath(root=movie_destination, module+'_movie'+mov_type) ; Movie names

say, threshold=1, silent=silent, 'created'+strcompress(cnt)+' '+module+' images'

; Create the movie. Currently movies can only be created on the Linux boxes.
; On NT mk_flick does not do anything.

FOR imov=0,nmov-1 DO BEGIN

    ; If fillsky is set then remove the first npad images. This is used for
    ; skysweeps: only after 24 hours the sky has been filled completely.
    ; (it's up to the caller to add a day to the duration of the movie).

    IF fillsky AND npad GT 0 THEN BEGIN
        say, threshold=0, silent=silent, 'remove '+strcompress(npad,/rem)+' leading frames from skysweep'
        tmp = do_file(/delete, frm_file[0:npad-1]+frm_type[imov],/silent)
    ENDIF

    tmp = frm_wild+frm_type[imov]

    CASE (file_search(tmp))[0] EQ '' OF
    0: BEGIN
        mk_flick, movie_file[imov], tmp, $
            silent  = silent                    , $
            /loop                               , $
            delay   = delay                     , $
            png     = mov_type[imov] EQ '.mng'  , $
            gif     = mov_type[imov] EQ '.gif'  , $
            mpeg    = mov_type[imov] EQ '.mpeg'

        IF NOT keep_frms THEN tmp = do_file(/delete, tmp, /silent)
    END
    1: movie_file[imov] = ''        ; Clear name for return argument
    ENDCASE

ENDFOR

RETURN  &  END